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

String Handling Module

1 view
Skip to first unread message

Fortran user

unread,
Apr 21, 2001, 10:51:33 AM4/21/01
to
Fortran beginners think very often that string handling is a painful task using
fortran. That is why I built the following string handling utilities for my
fortran90 courses. Answers to many questions in this newsgroup can be found in
the module below.

Please comment and send me improvements to this module.

I hope this helps.

Yours,
Fortran User.

MODULE String_handling

IMPLICIT NONE
PRIVATE

! This module contains String Handling procedures.
! Built and tested with Compaq Visual Fortran v6.1a
! Test platform: Windows98 second edition
! Usage: see 'test.f90'
!
! Please use or modify freely.
! Please send me feedback or improved versions of the module. Thank you.
! I'll repost the latest best version to comp.lang.fortran.
!
! Author: fortr...@aol.com
! release 001: spring 2001

PUBLIC :: OPERATOR(+), OPERATOR(.LTU.), OPERATOR(.UTL.)
PUBLIC :: ASSIGNMENT(=)

INTERFACE OPERATOR(+)
MODULE PROCEDURE concatenation
END INTERFACE

INTERFACE OPERATOR(+)
MODULE PROCEDURE string_plus_integer
END INTERFACE

INTERFACE OPERATOR(.LTU.)
MODULE PROCEDURE low_to_up_case
END INTERFACE

INTERFACE OPERATOR(.UTL.)
MODULE PROCEDURE up_to_low_case
END INTERFACE

INTERFACE ASSIGNMENT(=)
! MODULE PROCEDURE integer_to_string
MODULE PROCEDURE integer_to_string_padded
END INTERFACE

CONTAINS
! ========

FUNCTION concatenation (a, b) RESULT (x)
CHARACTER(LEN=*), INTENT(IN) :: a, b
CHARACTER(LEN=LEN(a)+LEN(b)) :: x

! Note the exception when a is one blank.
if (LEN(a) == 1 .AND. a == ' ') then
x=a//b
else
x=trim(a)//b
end if

END FUNCTION concatenation

FUNCTION string_plus_integer (a, b) RESULT (x)
CHARACTER(LEN=*), INTENT(IN) :: a
INTEGER,INTENT(IN) :: b
CHARACTER(LEN=LEN(a)+8) :: x
CHARACTER(LEN=8) :: integer_string
call integer_to_string(integer_string,b)
x=a+integer_string

END FUNCTION string_plus_integer

FUNCTION low_to_up_case (string) RESULT (x)
CHARACTER (len=*), INTENT(IN) :: string
CHARACTER (LEN=LEN(string)) :: x
INTEGER :: agcollat, apcollat, collat, offset, i, zpcollat
INTRINSIC char, ichar, len, max

apcollat = ichar ('a')
zpcollat = ichar ('z')
agcollat = ichar ('A')

offset = apcollat - agcollat
do i = 1, len (string)
collat = ichar (string (i:i) )
if ( (collat >= apcollat) .AND. (collat <= zpcollat) ) then
x (i:i) = char (collat - offset)
else
x (i:i) = string (i:i)
end if
end do

END FUNCTION low_to_up_case

FUNCTION up_to_low_case (string) RESULT (x)
CHARACTER (len=*), INTENT(IN) :: string
CHARACTER (LEN=LEN(string)) :: x
INTEGER :: agcollat, apcollat, collat, offset, i, zgcollat
INTRINSIC char, ichar, len, max

apcollat = ichar ('a')
agcollat = ichar ('A')
zgcollat = ichar ('Z')

offset = apcollat - agcollat
do i = 1, len (string)
collat = ichar (string (i:i) )
if ( (collat >= agcollat) .AND. (collat <= zgcollat) ) then
x (i:i) = char (collat + offset)
else
x (i:i) = string (i:i)
end if
end do

END FUNCTION up_to_low_case

SUBROUTINE integer_to_string(string,i)
CHARACTER(LEN=*), INTENT(OUT) :: string
INTEGER, INTENT(IN) :: i
CHARACTER(LEN=5) :: integer_format = '(Inn)'

if (len(string) > 0) then
write(integer_format(3:4),'(I2.2)')len(string)
write(string,integer_format)i
string=adjustl(string)
end if

END SUBROUTINE integer_to_string

SUBROUTINE integer_to_string_padded(string,i)
CHARACTER(LEN=*), INTENT(OUT) :: string
INTEGER, INTENT(IN) :: i
CHARACTER(LEN=8) :: integer_format = '(Inn.nn)'

if (len(string) > 0) then
write(integer_format(3:4),'(I2.2)')len(string)
integer_format(6:7)=integer_format(3:4)
write(string,integer_format)i
end if

END SUBROUTINE integer_to_string_padded

END MODULE String_handling

Program to test the above Module is the following:

PROGRAM Test

USE String_handling

INTEGER ::i
CHARACTER(LEN=8) :: istring, one, two, three
CHARACTER(LEN=11) :: filename

! Integer to string test
!-----------------------
print '(A)','>>>>> Integer to string test'
i=12345
istring=i
print *,istring

i=123456789
istring=i
print *,istring
pause

! Concatenation test
!-------------------
print '(A)','>>>>> Concatenation test'
one='abc'
two='def'
three=one+two
print *,three

three=one + ":" + two
print *,three
three=one + (" " + two)
print *,three
pause

! Upper/Lower Case test
!----------------------
print '(A)','>>>>> Upper/Lower Case test'
one='abc'
three=.LTU. one
print *,three

three=.UTL. three
print *,three
pause

! Other tests
print '(A)',"Other tests"
print *, .LTU. 'abc123defg'
print *, .UTL.(.LTU. 'abc123defg')
print *, .LTU.(.UTL.(.LTU. 'abc123defg'))

print *,"'abcd ' + '1234'"
print *,'abcd ' + '1234'
print *,"'abcd ' + ' 1234'"
print *,'abcd ' + ' 1234'
print *,'abc'+(' ' + (' ' +'def'))
pause

do i=1,10
filename='file'+i+'.dat'
print *,'Processing ',filename
end do
pause

END PROGRAM Test

@vic.bigpond.net.au Alan Miller

unread,
Apr 21, 2001, 8:34:37 PM4/21/01
to
Fortran user wrote in message
<20010421105133...@ng-mh1.aol.com>...

>Fortran beginners think very often that string handling is a painful task
using
>fortran. That is why I built the following string handling utilities for my
>fortran90 courses. Answers to many questions in this newsgroup can be found
in
>the module below.
>
>Please comment and send me improvements to this module.
>
>I hope this helps.
>
>Yours,
>Fortran User.
>

Just a few fairly minor comments.
1. I suggest that you insert IMPLICIT NONE into the test program.
2. PAUSE is no longer in the Fortran language.
3. You could make more use of LEN_TRIM instead of LEN.
4. You could add a subroutine to centre text in a string, e.g. for
use in headers. Perhaps this could be given as a class exercise
to teach the use of TRIM, ADJUSTL, LEN_TRIM, etc.
5. Compaq is not a good compiler for teaching.
ELF90 is much cheaper and forces the use of IMPLICIT NONE,
and generally forces students to use good programming practices.
N.B. You will also need to change PRINT to WRITE(*, *) and add
RETURN at the end of every subroutine and function.
F has a bigger advantage - it is free; it is also available for a wide
range of platforms. Both ELF90 and F force students to use the
newer features of Fortran denying the use of COMMON, DATA,
EQUIVALENCE, 3-way arithmetic IFs, computed GOTOs, etc.
F does not allow labels, while ELF90 does not allow CONTINUE.

P.S. Its now autumn 2001, but then perhaps you are in the wrong
half of the world!


--
Alan Miller, Retired Scientist (Statistician)
CSIRO Mathematical & Information Sciences
amiller @ bigpond.net.au
http://www.ozemail.com.au/~milleraj
http://users.bigpond.net.au/amiller/

@vic.bigpond.net.au Alan Miller

unread,
Apr 21, 2001, 8:59:38 PM4/21/01
to
Fortran user wrote in message
<20010421105133...@ng-mh1.aol.com>...
>Fortran beginners think very often that string handling is a painful task
using
>fortran. That is why I built the following string handling utilities for my
>fortran90 courses. Answers to many questions in this newsgroup can be found
in
>the module below.
>
>Please comment and send me improvements to this module.
>
>I hope this helps.
>
>Yours,
>Fortran User.
>
>
< Code deleted >

Another thought.

Much of the string handling which I do requires the use
of INDEX and SCAN - neither of these is used in the
module.
For instance, I frequently fill in computer forms which
require me to enter numbers such as credit card number,
account number, telephone number, etc.
They frequently tell you to enter the number exactly as shown
on an account, statement, etc. You do that and they reject
it because you entered the blanks and/or dashes or other
delimiters which they explicitly told you to enter!
So they need a little routine to scan for blanks, dashes,
and perhaps certain other characters (slashes, commas)
and remove them.

Cheers from a cold, wet Melbourne.

Greg Chien

unread,
Apr 22, 2001, 8:24:37 AM4/22/01
to
>===== Original Message From "Alan Miller" <amiller @ vic.bigpond.net.au>
=====

>Much of the string handling which I do requires the use
>of INDEX and SCAN - neither of these is used in the
>module.
>For instance, I frequently fill in computer forms which
>require me to enter numbers such as credit card number,
>account number, telephone number, etc.
>They frequently tell you to enter the number exactly as shown
>on an account, statement, etc. You do that and they reject
>it because you entered the blanks and/or dashes or other
>delimiters which they explicitly told you to enter!
>So they need a little routine to scan for blanks, dashes,
>and perhaps certain other characters (slashes, commas)
>and remove them.

Take a look at the "Masked String" specification in the String section in
the
following page:
http://protodesign-inc.com/SGmanuals/gui_control_data_representa.htm
(Sorry, I don't have a book mark to jump to the particular section directly.

This page contains all the input controls we do.)

Once the input mask is defined, the users cannot enter any "wrong"
characters
outside the defined set. One can follow the read/scan/verify/accept-reject
cycle for the whole string, but I think it would be friendlier to verify at
each type-in. Also, the input fields are displayed with the literal
characters (dashes, dots, slashes, commas, etc.), but the internal data have
all these literals removed. Better yet, this has been done for you ;-)

Regards,
Greg Chien
http://protodesign-inc.com

Fortran user

unread,
Apr 22, 2001, 11:08:36 AM4/22/01
to
Hi,

As you might see, the test program is only to test 'pause'and 'print' is quite
convenient for tests.

And the features you requested are done in my original 'String Handling'
procedures. Unfortunately for you, I sold them as a package to one of my
customers. I cannot post it 'as is', otherwise I could have some copyright
problem.

I have never used ELF90. I repeat to my trainees that the most important thing
in programming is not the programming language but their technical knowledge
and their DISCIPLINE. Therefore, IMHO using ELF90 only to force IMPLICIT NONE
is not necessary.

Concerning the cost of a compiler, I always tell my trainees that the most
expensive in software development is their salary. So I suggest them to choose
whatever development platform that fits better their personnality. If they
respect the 'fortran standard' and the good sense, the resulting fortran source
can be compiled using the best comipler for the target platform using the
command line. For example I propose them to use CVF because the IDE is very
convenient and the on line help is excellent. Most of them work in industries
with supercomputers etc. The majority of them fall in love with CVF and
SourceSafe from Microsoft (this is not an ad ! Hi, Steve Lionel can I have a
commission for my effort ?).

I told them that the cost of a CVF compiler is less than their monthly wage.
So, why bother with compiler cost ? I show them how to write code in CVF and to
compile and run it on Unix-like computer using the user tool of CVF plus some
ftp's and rexec's after syntaxic and semantic check on their PC. They are HAPPY
!!

RETURN is not required. In my course it is simply NOT mentioned. The rule is
that one routine has only one entry (SUBROUTINE, FUNCTION etc) and only one
exit (that is END SUBROUTINE or END FUNCTION).

END has always something behind (END IF, END DO, END MODULE modulename etc).

arithmetic IFs, CONTINUE, COMMON, DATA, EQUIVALENCE, GO TO, SAVE, END= in READ
etc are not included in my courses. I simply don't mention them. In my mind it
is useless to teach these fortran substleties. Usually when fortran is taught
correctly, they don't even see the need to use them. Almost in all my courses I
see that I the problem IS NOT with the language itself but with their logic.

The fact that you mentioned the above mentioned elements of fortran shows that
you might have met some problems with them. We haven't because we don't use
them.

I repeat that the most important and expensive part of programming is the
HUMAN. Source code is written to be human readable. The only suggestionI give
on how fortran code should be written (CAPS or not) is that it should be easily
read by the TEAM in which they are working.

I prefer, since several month, to code in uppercase only for the declaration
part of a module (SUBROUTINE, variable declarations etc) and the END .... part.
The reason ois quite simple: You can see quickly where a routine starts and
where it ends. The fortran standard does not distinct CAPs and lower case.

It is springtime in Europe. Have a nice autumn !

Fortran user

unread,
Apr 22, 2001, 11:11:01 AM4/22/01
to
I have a separate module for token parsing using fortran before
semantic/syntaxic analysis. Unfortunately, it is used in one of our software.
I can't post them 'as is'. Sorry.

Dan Tex1

unread,
Apr 22, 2001, 1:00:18 PM4/22/01
to
>From: "Alan Miller" amiller@ vic.bigpond.net.au
>
>Just a few fairly minor comments.
>1. I suggest that you insert IMPLICIT NONE into the test program.
>2. PAUSE is no longer in the Fortran language.

Actually, I believe PAUSE is still part of the language, though
it is marked as obsolescent.

Dan :-)

Fortran user

unread,
Apr 22, 2001, 2:08:53 PM4/22/01
to
I forgot to mention that 'print' and 'pause' are convenient because you can
find them easily when you have finished with your tests. You know that prints
and pauses have to be deleted.

Otherwise you have to look for all reads and all writes and see whether you
have to delete them or not, just imagine that you deleted one line containing
important 'write'.

@vic.bigpond.net.au Alan Miller

unread,
Apr 22, 2001, 7:05:17 PM4/22/01
to
Dan Tex1 wrote in message <20010422130018...@ng-fq1.aol.com>...

Dan,
I don't have a copy of the current Fortran standard, though I do
have the F90 standard and the draft F2004(?) standard.
F90 declared pause as obsolescent (appendix B).
I believe that the obsolescent features were deleted in F95.
Both NAS FortranPlus and Compaq Fortran tell me that
pause has been deleted.

Cheers

Dan Tex1

unread,
Apr 23, 2001, 11:59:24 AM4/23/01
to
>From: "Alan Miller" amiller@ vic.bigpond.net.au
>
>Dan Tex1 wrote in message <20010422130018...@ng-fq1.aol.com>...
>>>From: "Alan Miller" amiller@ vic.bigpond.net.au
>>>
>>>Just a few fairly minor comments.
>>>1. I suggest that you insert IMPLICIT NONE into the test program.
>>>2. PAUSE is no longer in the Fortran language.
>>
>>Actually, I believe PAUSE is still part of the language, though
>>it is marked as obsolescent.
>>
>>Dan :-)
>
>Dan,
>I don't have a copy of the current Fortran standard, though I do
>have the F90 standard and the draft F2004(?) standard.
>F90 declared pause as obsolescent (appendix B).
>I believe that the obsolescent features were deleted in F95.
>Both NAS FortranPlus and Compaq Fortran tell me that
>pause has been deleted.
>
>Cheers

Alan. You are correct. I was mistaken. Lahey's LF95 manual list it as
obsolecent and though I looked in the "Fortran95 Handbook..." I somehow missed
it. I now have found it in the handbook and it is indeed listed as deleted (
though I do believe the F95 Handbook was printed before the 95 standard was
official adopted? ).

Dan :-)

James Giles

unread,
Apr 23, 2001, 1:16:00 PM4/23/01
to

"Alan Miller" <amiller @ vic.bigpond.net.au> wrote in message
news:NsJE6.8125$ff.6...@news-server.bigpond.net.au...
...

> I don't have a copy of the current Fortran standard, though I do
> have the F90 standard and the draft F2004(?) standard.
> F90 declared pause as obsolescent (appendix B).
> I believe that the obsolescent features were deleted in F95.
> Both NAS FortranPlus and Compaq Fortran tell me that
> pause has been deleted.

There were nine obsolescent features listed in F90. Only five
of these were deleted in F95. Five more were added to the
obsolescent list (which still contains nine items). The deleted
features are:

1) REAL and DOUBLE PRECISION DO variables
2) Branching to an END IF statement
3) PAUSE statement
4) ASSIGN and assigned GOTO statements
5) The H format edit descriptor

Rumor has it that no additions to either the deleted or the
obsolescent list are likely.

--
J. Giles


Ross Bogue

unread,
Apr 25, 2001, 10:03:10 AM4/25/01
to
In article
<krZE6.32088$RF1.2...@bgtnsc06-news.ops.worldnet.att.net>, James
Giles <James...@worldnet.att.net> wrote:

> There were nine obsolescent features listed in F90. Only five
> of these were deleted in F95. Five more were added to the
> obsolescent list (which still contains nine items). The deleted
> features are:
>
> 1) REAL and DOUBLE PRECISION DO variables
> 2) Branching to an END IF statement
> 3) PAUSE statement
> 4) ASSIGN and assigned GOTO statements
> 5) The H format edit descriptor


Thanks, James!

Out of curiosity, what were the other four? And what are the new five?


Ross

Dick Hendrickson

unread,
Apr 25, 2001, 10:48:06 AM4/25/01
to

Arithmetic (3 branch) IF
Shared DO termination
Alternate Return
Assigned Format specifiers--actually, this was also deleted.
It's listed as a separate item (8) in the F90 obsolescent list,
but when F95 deleted the ASSIGN statement the assigned format
also went away by magic. Anyhow, my F95 lists it in (4) of the
deleted features

>And what are the new five?

Computed GOTO
Statement Functions
DATA statements amongst executable statements
Assumed length character functions
Fixed form source
CHARACTER* form of CHARACTER

There are 6 new ones, not 5.

Dick Hendrickson
>
> Ross

James Giles

unread,
Apr 25, 2001, 11:20:56 AM4/25/01
to

"Ross Bogue" <rbo...@entropy.phy.ilstu.edu> wrote in message
news:250420010903101952%rbo...@entropy.phy.ilstu.edu...

This is the presentlist of obsolescent features. I don't remember
which ones were added in F95, since I only have my F95 doc with
me and can't compare it to F90.

(1) Arithmetic IF - use the IF statement (8.1.2.4) or IF construct (8.1.2).

(2) Shared DO termination and termination on a statement other than END DO or
CONTINUE - use an END DO or a CONTINUE statement for each DO statement.

(3) Alternate return

(4) Computed GO TO statement

(5) Statement functions

(6) DATA statements amongst executable statements

(7) Assumed length character functions

(8) Fixed form source

(9) CHARACTER* form of CHARACTER declaration

I would argue that the alternate return doesn't fit the definition
of obsolescent and doesn't belong on the list (until a general
exception handling feature is included). But, that's another
line of inquiry that oft goes ballistic in this group.

--
J. Giles


David Spurr

unread,
Apr 25, 2001, 6:42:06 PM4/25/01
to
Dick Hendrickson <dick.hen...@att.net> wrote:


>
>>And what are the new five?
> Computed GOTO
> Statement Functions
> DATA statements amongst executable statements
> Assumed length character functions
> Fixed form source
> CHARACTER* form of CHARACTER
>
>There are 6 new ones, not 5.

What is so bad about items 2, 5 & 6 that marks them for obsolescence /
possible deletion ? (& 4? )

Person preference of an elite ? Desire to make code obsolescent ?
Desire to press more keys ? Not pretty ? (character*9 cf
character(9) !!!!) What fundamental law of computer language is
broken - I fail to see what this achieves - other than adding another
character & requiring a couple of shift keystrokes.

Thats a huge amount of code declare obsolescent.

Bill

unread,
Apr 25, 2001, 7:18:53 PM4/25/01
to

David Spurr wrote:

Note that they were declared obsolescent not deleted from the language.
The standard still requires compilers to support them, and the strong
expectation is that the next standard will require support for all of
hem. Problems I have with them that suggests that they should be
obsolescent.

Computed GOTO can easilly generate hard to follow program flow, and can
be difficult to maintain. It has the tendency to accidently fall through
similar to C's switch. SELECT CASE is almost always better for the
contexts in which computed GOTO is used..

The syntax of statement functions is very similar to array assignment,
making them difficult to recognize and hence maintain. This is a large
complication, relative to its useage, in the syntactic and semantic
analysis of Fortran codes.

Requiring separation of executable statements from other statements can
make it easier to locate and maintain some forms of statements.

Assumed length character functions were extremely rarely used

Fixed form source is more error prone due to insignicant white space,
lack of definition of the effects of tabs, and ease of writing past
column 72. It greatly complicates the lexical analysis of Fortran
hindering the development of simple tools. There exist a number of codes,
that have been extremely well tested, for converting to free form.

CHARACTER* form of CHARACTER is deprecated mainly as an irregularity. In
the early 80's the standards committees looked at the syntactic
complexities and semantic ambiguities introduced by STARTRAN and decided
not to include REAL*, INTEGER*, etc., in the language. This left
CHARACTER* as an odd appendage, but not as a major source of errors. It
is, however, extremely easilly converted to the other forms by automated
tools, and the amount of effort to type CHARACTER(9) relative to
CHARACTER*9 is so trivial they could not imagine significant objections.


bv

unread,
Apr 25, 2001, 10:03:34 PM4/25/01
to
Bill wrote:
>
> The syntax of statement functions is very similar to array assignment,
> making them difficult to recognize and hence maintain. This is a large
> complication, relative to its useage, in the syntactic and semantic
> analysis of Fortran codes.

If those two look similar to someone then that someone should be a short
order cook rather than dabbling with Fortran redesign. I can't see the
logic behind that reasoning, so please indulge us with explaining those
fatal *similarities*. e.g.

g(h) = 9.80665*(1 - 3.13671*e-7*h)

btw, don't arrays usually require dimensioning or is that also slated to
go...

--
Dr.B.Voh
------------------------------------------------------
Applied Algorithms http://sdynamix.com

Dick Hendrickson

unread,
Apr 26, 2001, 10:47:06 AM4/26/01
to
bv wrote:
>
> Bill wrote:
> >
> > The syntax of statement functions is very similar to array assignment,
> > making them difficult to recognize and hence maintain. This is a large
> > complication, relative to its useage, in the syntactic and semantic
> > analysis of Fortran codes.
>
> If those two look similar to someone then that someone should be a short
> order cook rather than dabbling with Fortran redesign. I can't see the
> logic behind that reasoning, so please indulge us with explaining those
> fatal *similarities*. e.g.
>
> g(h) = 9.80665*(1 - 3.13671*e-7*h)
>
> btw, don't arrays usually require dimensioning or is that also slated to
> go...
>

It isn't 100% true that statement functions have no good features,
rather
they have enough warts and irregularities to cross the boundary for
many people.

1) To my eye, they do look like arrays:

real q(10)
integer h
...


g(h) = 9.80665*(1 - 3.13671*e-7*h)

q(h) = 9.80665*(1 - 3.13671*e-7*h)

It's hard to see a big difference there, especially in a big code with
a few pages of declarations or includes or use statements when the
dimension statement might not be easy to spot.

2) It can cause a funny error if the first line has a spelling error

mispelled_array_name(i,j) = other_array(i,j)

Is that a function definition or a programming error?

3) The arguments get their type from the host, but aren't really
the host variables. In the past this caused hard to find problems
when the dummy arguments were implicitly typed and the code was
enlarged by adding a "new" variable in the host and typing it with
a non-default type. Easy to do if a code is maintained by more than
one person or over a few months or if a module brings in a variable.

All of these can be avoided by careful programming; but why
encourage/continue something that can be hard to use? It isn't
likely that compilers will drop support for statement functions
in the near future.

Dick Hendrickson

Bill

unread,
Apr 26, 2001, 1:19:31 PM4/26/01
to

bv wrote:

> Bill wrote:
> >
> > The syntax of statement functions is very similar to array assignment,
> > making them difficult to recognize and hence maintain. This is a large
> > complication, relative to its useage, in the syntactic and semantic
> > analysis of Fortran codes.
>
> If those two look similar to someone then that someone should be a short
> order cook rather than dabbling with Fortran redesign. I can't see the
> logic behind that reasoning, so please indulge us with explaining those
> fatal *similarities*. e.g.
>
> g(h) = 9.80665*(1 - 3.13671*e-7*h)
>
> btw, don't arrays usually require dimensioning or is that also slated to
> go...

> <snip>

Dick Hendrickson has already addressed most of this but I want to put in my
two cents anyway.

Of course they look similar. The statement function is distinguished from
an array assignment only because an additional proceeding statement (an
array declaration) is missing. It is error prone to interpret something
from what is not there, particularly if what you are trying to recognize is
something you don't often use, and in practice statement functions are not
often used. It is one of the few syntactic aspects of the language (such as
the lack of significant blanks in fixed form and unreserved keywords) that
can only be recognized by semantic analysis, and as such complicates the
development of syntactic analysis of fortran far more than many other
language aspects, It would be different if statement functions had an
explicit declaration, e.g,

FUNCTION g(h) = 9.80665*(1 - 3.13671*e-7*h)

It might have also been different if they had more flexible semantics or
syntax, i.e., could used as arguments to procedures, definitions that
exended over more than one "statement" so that they could incorporate more
complicated functionality (difficult to define in a statement oriented
language such as Fortran), or could appear outside the body of subprograms.
With more flexibility they would be more widely used. Perhaps even if they
had less flexible semantics, i.e., their arguments could not be integers,
they would be less confusing.

In deprecating them it would have been useful if the standard had provided
an alternative, less wordy, syntax for simple internal fuctions, say

FUNCTION g(h) = 9.80665*(1 - 3.13671*e-7*h)

so that replacing statement functions with internal functions would be less
of a pain. But again the standard bodies do not, at this time, propose
eliminating statement functions in F200x . Given the decline in standards
participation it is becoming increasingly unlikely that an F201x will
appear, or that if it does appear, that it will be more than a very minor
revision. I would be very surprized if the standards bodies ever deleted
statement functions.

0 new messages