1) Consider this example sub: (accepts m,n and returns w)
Subroutine Test(w,m,n)
integer m,n
real w
real x(m)
real y(m,n)
real z(m,m,n)
!.....................................
w = whatever
!....................................
return
end subroutine Test
2) Couldn't find any sample code in ref fortran texts that uses
similar declarations.
The above example does not appear to cause compiler or run-time
errors, but I believe it is not a standard fortran (F77, g95).
Does the standard (F77 or later) say anything in that regard ?
Thank you.
Monir
troutmask:sgk[205] cat k.f90
program k
integer m, n
real w
m = 2
n = 2
call sub(m, n, w)
print *, w
end program k
subroutine sub(m, n, w)
real x(m, n)
x = 1
w = sum(x)
end subroutine sub
troutmask:sgk[206] gfc4x -o z k.f90
troutmask:sgk[207] ./z
4.0000000
Do you have an actually example that exhibits
whatever problem you've hit?
--
steve
I believe added in Fortran 90 or 95. (And added to C in C99.)
They are called 'automatic arrays', so look them up under that name.
Fortran 77 is consistent (but does not require) static allocation
for everything.
-- glen
> The answer is probably NO!
The answer is yes as of f90. As Glen says, this was added to the
standard in f90. Many later f77 compilers also allowed it as an
extension. Look up "automatic array" or "automatic variable" in the
texts.
--
Richard Maine | Good judgment comes from experience;
email: last name at domain . net | experience comes from bad judgment.
domain: summertriangle | -- Mark Twain
>
> 2) Couldn't find any sample code in ref fortran texts that uses
> similar declarations.
MR&C, p. 100.
Regards,
Mike Metcalf
and
Guide to Fortran 2003 Programming, p. 119
The Fortran 2003 Handbook, p. 117.
:-)
Walt Brainerd
Look in any Fortran 90 text.
>The above example does not appear to cause compiler or run-time
>errors, but I believe it is not a standard fortran (F77, g95).
It's standard from Fortran 90.
>Does the standard (F77 or later) say anything in that regard ?
Dynamic arrays were introduced in F90.
> The answer is probably NO!
This may seem like a minor nit, but no poster has yet directly
answered the O.P.'s question. Thus:
C:\gfortran\clf\dimtest>type dimtest.f90
program test
call dimtest(5)
end program test
subroutine dimtest(i)
integer(selected_int_kind(9)) i
integer(selected_int_kind(18)) A(3)
A = [4*atan(1.0)+[(i,i=1,size(A))]]
write(*,'(a,3(i0:","))') 'Before DIM: A = ',A
write(*,'(a,i0,a,i0)') 'KIND(A) = ', KIND(A), ', KIND(i) = ',KIND(i)
A = DIM(A,i)
write(*,'(a,3(i0:","))') 'After DIM: A = ',A
end subroutine dimtest
C:\gfortran\clf\dimtest>gfortran -Wall dimtest.f90 -odimtest
C:\gfortran\clf\dimtest>dimtest
Before DIM: A = 4,5,6
KIND(A) = 8, KIND(i) = 4
After DIM: A = 0,0,1
As a special bonus we find that gfortran doesn't warn about an
undocumented extension in this example.
--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end
> "monir" <mon...@mondenet.com> wrote in message
> news:f0869e8e-790e-4e52...@t19g2000vbc.googlegroups.com...
>
> > The answer is probably NO!
>
> This may seem like a minor nit, but no poster has yet directly
> answered the O.P.'s question. Thus:
[example of using the dim intrinsic on a local array using an argument
list integer]
Lest this confuse the OP, let me note that the slightly obscure DIM
intrinsic has nothing to do with dynamic dimensioning of arrays, which
is what I thought it fairly clear the question was about. James is
taking the subject line's mention of DIM as being literal rather than as
an abbreviation for dimension.
I'm not quite sure whether this was intended as a humorous comment on
the possible ambiguity of the subject line out of context or whether he
skimmed quickly enough that he actually thought this was the question.
(I'll mention the possibility that it actually was the question just
long enough to dismiss it as seeming implausible to me, given the body
of the OP's post.)
> C:\gfortran\clf\dimtest>gfortran -Wall dimtest.f90 -odimtest
>
> C:\gfortran\clf\dimtest>dimtest
> Before DIM: A = 4,5,6
> KIND(A) = 8, KIND(i) = 4
> After DIM: A = 0,0,1
>
> As a special bonus we find that gfortran doesn't warn about an
> undocumented extension in this example.
>
-Wall does not imply -std=f95.
--
steve
This has nothing to do with the OP's question.
"Dim" is an abbreviation for "Dimension".
His example makes it absolutely clear.
The problem, somewhat facetiously, seems to be that after steadfastly
ignoring people's advice to join the modern world and use dynamic
memory allocation to make his life easier, the OP has now all by
himself stumbled onto one limited form of dynamic memory, realized
that it could be useful, and is hence wondering where the gotcha
is. After all, programming is supposed to be a painful exercise in
frustration.
--
JB
The one caveat is this: automatic arrays are usually implemented
by compiler writers using the stack, and one OS family in particular --
MS Windows -- hard-codes the stack size to a ridiculously small 512MB.
If you do serious modeling (weather, land surface, air quality, etc.),
this will be a serious problem there.
Some compilers implement an "allocate large automatic arrays off
the heap" strategy that has more call-overhead but gets around
problems of this sort, but impacts project portability. See your
vendor's documentation.
FWIW -- Carlie Coats
1) Shortly before retrieving your replies and being unsure what the
answer would be, I tried a Parameter statement in the example Sub Test
() ; specifying the maximum anticipated subscripts "m" and "n" for the
local arrays.
I got different results, which is very confusing, and I've been
working on the problem since then !!!
2) OP example:
Subroutine Test(w,m,n) !m=10, n=20
integer m,n
real w
real x(m)
real y(m,n)
real z(m,m,n)
!.....................................
w = whatever
!....................................
return
end subroutine Test
Modified:
Subroutine Test_2(w)
integer m,n, maxm, maxn
Parameter (maxm=30, maxn = 30)
real w
real x(maxm)
real y(maxm,maxn)
real z(maxm,maxm,maxn)
!.....................................
w = whatever
!....................................
return
end subroutine Test_2
3) In the real situation (actual code), the individual routines works
fine in isolation, but not in the following combination, which may
suggest that the variable arrays are not manipulated/passed correctly
(dimension-wise) and perhaps the problem is not a dynamic array issue
after all. Or is it ??
(F77 & g95)
3) Here're the troublesome DECLARATION sections of the code:
! ************************************************************
SUBROUTINE Splint3d(x1a, x2a, x3a,
1 ya, maxPln,maxR,maxTH,
2 k, m, n,
3 x1, x2, x3, Z)
! ************************************************************
! USES: Splie2d , Splin2d , Splined , Splintd
integer k,m,n
integer maxPln,maxR,maxTH
integer i,j,kk
integer kmax,mmax,nmax,nop
double precision x1,x2,x3, Z
double precision d1,dn
! ...the following 4 arrays are dim exactly as in the calling
! ...routine and are printed correctly in this routine
double precision x1a(maxPln),x2a(maxR),x3a(maxTH)
double precision ya(maxPln,maxR,maxTH)
double precision y(maxR,maxTH), y2a(maxR,maxTH)
double precision ytmp(maxPln), y2tmp(maxPln)
do 13 i=1, k
do 12 j=1, m
do 12 kk=1, n
y(j,kk) = ya(i,j,kk)
12 continue
call splie2d (x2a,x3a, y , maxR, maxTH, m, n, y2a)
call splin2d (x2a,x3a, y , y2a , maxR, maxTH, m,n, x2,x3,ytmp(i))
13 continue
call splined (x1a, ytmp , k, d1, dn, y2tmp)
call splintd (x1a, ytmp , y2tmp ,k,x1,z)
Return
End Subroutine Splint3d
!************************************************************
SUBROUTINE SPLIE2d(x1a, x2a, ya,maxM,maxN, m, n,y2a)
!************************************************************
! USES: Splined
integer maxM,maxN,m,n
integer nn,nop,j,k
parameter (nn=100)
double precision d1,dn
double precision x1a(maxM), x2a(maxN)
double precision ya(maxM,maxN), y2a(maxM,maxN)
double precision ytmp(nn),y2tmp(nn)
do 13 j=1, m
do 11 k=1,n
ytmp(k) = ya(j,k)
11 continue
call splined(x2a,ytmp,n, d1, dn,y2tmp)
do 12 k=1, n
y2a(j,k) = y2tmp(k)
12 continue
13 continue
return
End Subroutine SPLIE2d
!************************************************************
SUBROUTINE SPLIN2d(x1a,x2a, ya, y2a, maxM,maxN, m,n,x1,x2,y)
!************************************************************
! USES: Splintd , Splined
integer maxM,maxN,m,n
integer nn,nop,j,k
parameter (nn=100)
double precision d1,dn,x1,x2,y
double precision x1a(maxM), x2a(maxN)
double precision ya(maxM,maxN),y2a(maxM,maxN)
double precision ytmp(nn),y2tmp(nn)
double precision yytmp(nn)
do 12 j=1, m
do 11 k=1, n
ytmp(k) = ya(j,k)
y2tmp(k) = y2a(j,k)
11 continue
call splintd(x2a,ytmp,y2tmp,n,x2,yytmp(j))
12 continue
call splined(x1a,yytmp,m, d1, dn,y2tmp)
call splintd(x1a,yytmp,y2tmp,m,x1,y)
return
End Subroutine SPLIN2d
C ******************************************************************
SUBROUTINE SPLINEd(X, Y, N, YP1, YPN, Y2)
C ******************************************************************
implicit double precision (a-h,o-z)
dimension X(N),Y(N),Y2(N)
!..............code...............................
return
End
C ******************************************************************
SUBROUTINE SPLINTd(XA, YA, Y2A, N, X, Y)
C ******************************************************************
implicit double precision (a-h,o-z)
dimension XA(N), YA(N), Y2A(N)
!..............code...............................
return
end
I apologize for the lengthy posting.
Please ignore the question if it is an "obsolete F77" time-consuming
question!
Hopefully someone would be able to identify the problem with minimum
time/effort.
That would be greatly appreciated.
Thank you kindly.
Monir
<snip>
>
> 3) In the real situation (actual code), the individual routines works
> fine in isolation, but not in the following combination, which may
> suggest that the variable arrays are not manipulated/passed correctly
> (dimension-wise) and perhaps the problem is not a dynamic array issue
> after all. Or is it ??
> (F77 & g95)
>
> 3) Here're the troublesome DECLARATION sections of the code:
<snip>
> I apologize for the lengthy posting.
> Please ignore the question if it is an "obsolete F77" time-consuming
> question!
> Hopefully someone would be able to identify the problem with minimum
> time/effort.
> That would be greatly appreciated.
>
> Thank you kindly.
> Monir
It is highly likley that the maximum return on time/effort will be obtained
by putting all the code shown (and that I have snipped) into a single
module (even if this is only for experimental purposes). This will ensure
every routine has an "explicit interface", and so allow the compiler to
diagnose most (or all) possible errors of the type you appear to be
describing.
--
Qolin
Email: my qname at domain dot com
Domain: qomputing
> 3) In the real situation (actual code), the individual routines works
> fine in isolation, but not in the following combination, which may
> suggest that the variable arrays are not manipulated/passed correctly
> (dimension-wise) and perhaps the problem is not a dynamic array issue
> after all. Or is it ??
I didn't tak ethe time to trace everything through, but it didn't take
much time at all to find at least one example of an array that was not
declared consistently in the caller and the callee. That suggests there
are likely to be more. I'm not going to try to track them down for you.
I suggest just sitting down and looking at every one. The first example
I noticed was
...
> double precision ytmp(maxPln), y2tmp(maxPln)
...
> call splined (x1a, ytmp , k, d1, dn, y2tmp)
...
> SUBROUTINE SPLINEd(X, Y, N, YP1, YPN, Y2)
...
> dimension X(N),Y(N),Y2(N)
So y2tmp is dimensioned maxPln in the caller, but maxPln is not even
passed to splined. Instead, k is passed and used (as the dummy named n)
to dimension the y2 dummy argument.
This stuff isn't rocket science. Quite the opposite, it is nothing other
than taking the time to sit down and look. *AT EACH AND EVERY CASE*. The
actual and dummy should agree. I just showed how to look at one. I
suggest doing all the rest. Not worth my time. (Insert comment about
teaching people how to fish instead of giving them a fish; I feel my
time is better spent in my showing what to look for than in my finding
it for you. No, I didn't find it and refuse to say where - I just
stopped looking after seeing the above case.) Odds are that this one
isn't actually a problem, but I take it as symptomatic of a style that
probably will cause problems elsewhere.
Perhaps you might think that k and maxPln are supposed to have the same
value, but to me that doesn't matter. Making assumptions like that all
over the place is exactly how one gets into such troubles. Every
assumption like that is something that needs to be verified. Any such
assumptions should certainly be explicitly stated in comments in the
code - probably with exclamation marks. Better yet is not to make such
assumptions. If two things are supposed to be the same, then make them
the same or have the code test the values.
So look at every declaration, comparing the actual and dummy. Don't
count on any assumptions about what ought to be. Just look directly at
the exact declarations. If they don't match, then figure that's a likely
source of problem.
Along the same line, it has been mentioned here many times that implicit
typing is prone to error. Even more prone to error is randomly mixing
styles, using implicit typing some places and exlicit typing elsewhere.
That kind of thing makes consistency much harder to check. The more you
make the actual and dummy declarations done the same way, the more
obvious problems will be.
> 1) Shortly before retrieving your replies and being unsure what the
> answer would be, I tried a Parameter statement in the example Sub Test
> () ; specifying the maximum anticipated subscripts "m" and "n" for the
> local arrays.
> I got different results, which is very confusing, and I've been
> working on the problem since then !!!
[snip]
Immediately the chief suspect is that your acutal arguments are not the same
as your formal arguments.
[snip]
for example:
> SUBROUTINE SPLINTd(XA, YA, Y2A, N, X, Y)
> implicit double precision (a-h,o-z)
> dimension XA(N), YA(N), Y2A(N)
is called with the assumption that XA, YA and Y2A are the same size, yet in
several calling programs
the passed arrays are dimensioned with DIFFERENT variables, which I expect
are NOT constrained to be the same size.
--- e
e p chandler wrote:
>> SUBROUTINE SPLINTd(XA, YA, Y2A, N, X, Y)
>> implicit double precision (a-h,o-z)
>> dimension XA(N), YA(N), Y2A(N)
>is called with the assumption that XA, YA and Y2A are the same size, yet in
>several calling programs
>the passed arrays are dimensioned with DIFFERENT variables, which I expect
>are NOT constrained to be the same size.
But for 1D arrays, one DOES NOT have to pass the declared and actual
sizes to the called routines. Only the actual sizes.
The problem is most likely associated with the declaration/passing of
the 2D and 3D arrays.
Regards.
Monir
Regards.
Monir
---> Yes, you can get away with DIMENSIONING the 1D arrays in your
subroutines to (1). Yes you can pass a 1D array that is actually longer than
that declared.
But why?
-- e
> But for 1D arrays, one DOES NOT have to pass the declared and actual
> sizes to the called routines. Only the actual sizes.
Which is why I said
>> Odds are that this one isn't actually a problem
> The problem is most likely associated with the declaration/passing of
> the 2D and 3D arrays.
Most likely. But note that I also said
>> but I take it as symptomatic of a style that
>> probably will cause problems elsewhere.
You should get in the habit of always coding correctly - not just
guessing when you have to and when you can get by without it. For a
start, you will guess wrong. For example, there are cases where you can
get in trouble with 1D arrays. Copy-in/copy-out can cause havoc with
incorrect dimensions even in 1D.
But more important is the human factor - that bit about getting in the
habit. If you are in the habit of being sloppy about things where they
don't matter, you will end up being sloppy about them elsewhere at
times, and it will bite you. This is almost inevitable.
That's why I stopped when I found one case. Even though odds are that
case isn't your problem
1. Maybe it is
2. But more importantly, it makes me guess that something like it
elsewhere is probably the problem.
If you can't take the trouble to be careful about such things yourself,
I decline to take my time to search further myself. I long ago
discovered the truth of the well-known adage that it takes less time to
do the job right in the first place than to deal with the consequences
of doing it sloppily. That is very true in programming. My personal
productivity sure went up a lot when I started making it a habit to
check every line for obvious errors when I wrote it in the first place.
One of those checks is making sure that arguments agree in such things
as dimensions. (F90 assumed shape makes it a lot easier to get such
things right, I might add).
The above code does not use dynamic arrays.
These issues were discussed at length and explained in the post
"Could this result in array distortion"
that you inititiated.
That was a mid-1960s hack for adjustable dimensions - long since
obsolete.
Monir was not talking about that.
For adjustable dimensions (F77) the array is dimensioned
with a variable for its bound, and that variable and the array
are dummy arguments.
> Robin wrote:
> That was a mid-1960s hack for adjustable dimensions - long since
> obsolete.
> Monir was not talking about that.
>
> These issues were discussed at length and explained in the post
> "Could this result in array distortion"
> that you inititiated.
Robin;
1) In the earlier post: "Can this result in array distortion ??", the
question was regarding passing multidimensional arrays with diffirent
sizes than those declared in the calling routine.
Here the question is regarding using argument list integers to dim
local multidimensional arrays.
NOT the same!
2) It appears at this point and after extensive numerical
experimentation that the problem might actually be associated with
some kind of "numerical instability" rather than a code issue. The
reason for this tentative conclusion is that my algorithm (F77) works
fine under "certain conditions", which I'm trying to find out.
3) For example, if I pass fictitious data values for the 3D array
"ya" (same dimensions, and everything else remain UNCHANGED) to the
main routine:
! ************************************************************
SUBROUTINE Splint3d(x1a, x2a, x3a,
1 ya, maxPln,maxR,maxTH,
2 k, m, n,
3 x1, x2, x3, Z)
! ************************************************************
! USES: Splie2d , Splin2d , Splined , Splintd
the program works perfectly, producing the correct results (up to
11-12 decimal figures), while using the actual analytical data for
"ya" (with no singularities or jump discontinuities), it produces
rubbish!
Keep in mind that the only thing that's changing here is the values of
the 3D array "ya".
(..the above 4 arrays: x1a(1D),x2a(1D),x3a(1D),ya(3D) are dim exactly
as in the calling routine, as pointed out in my post Dec 20, 4:46 pm))
Earlier, JB wrote:
> After all, programming is supposed to be a painful exercise in frustration.
I entirely agree!!
Regards.
Monir
OK, although I would like to be able to warn about nonstandard
intrinsics or procedures somehow without referring to a specific
standard (-std=f95 wouldn't work here because it prints out
extraneous errors) this is a vendor choice and no worse than
the warning capacity of ifort, for example.
But I wanted to call attention to the undocumented part. In
the gfortran manual there is no indication that the following
program should work and if it did, what the KINDs of the results
would be. Also DIM is not listed as a specific name there,
although the compiler does consider it to be one, consistent
with the standard.
C:\gfortran\clf\dimtest>type integer.i90
subroutine itest(comment,x)
integer(ik) x
character(*) comment
write(*,'(2a,i0,a,i0)') comment,&
' Type of variable: INTEGER, Kind = ',ik,', value = ',x
end subroutine itest
C:\gfortran\clf\dimtest>type real.i90
subroutine rtest(comment,x)
real(rk) x
character(20) fmt
character(*) comment
write(fmt,'(a,i0,a,i0,a)') &
'(2a,i0,a,g',precision(x)+7,'.',precision(x),')'
write(*,fmt) comment,&
' Type of variable: REAL, Kind = ',rk,', value = ',x
end subroutine rtest
C:\gfortran\clf\dimtest>type test2.f90
module mykinds
implicit none
integer, parameter :: ik4 = selected_int_kind(9)
integer, parameter :: ik8 = selected_int_kind(18)
integer, parameter :: sp = selected_real_kind(6,30)
integer, parameter :: dp = selected_real_kind(15,300)
end module mykinds
module i4mod
use mykinds, only: ik => ik4
implicit none
private
public test
interface test
module procedure itest
end interface test
contains
include 'integer.i90'
end module i4mod
module i8mod
use mykinds, only: ik => ik8
implicit none
private
public test
interface test
module procedure itest
end interface test
contains
include 'integer.i90'
end module i8mod
module r4mod
use mykinds, only: rk => sp
implicit none
private
public test
interface test
module procedure rtest
end interface test
contains
include 'real.i90'
end module r4mod
module r8mod
use mykinds, only: rk => dp
implicit none
private
public test
interface test
module procedure rtest
end interface test
contains
include 'real.i90'
end module r8mod
module generic_recombination
use i4mod, only: test
use i8mod, only: test
use r4mod, only: test
use r8mod, only: test
end module generic_recombination
program test2
use mykinds
use generic_recombination
implicit none
integer(ik4) i4x, i4y
integer(ik8) i8x, i8y
real(sp) r4x, r4y
real(dp) r8x, r8y
character(20) comment
intrinsic DIM
i4x = 11
i4y = 7
i8x = 11
i8y = 7
r4x = 11
r4y = 7
r8x = 11
r8y = 7
write(comment,'(a,i0,a,i0,a,i0,a,i0,a)') &
'DIM(',i4x,'_',kind(i4x),',',i8y,'_',kind(i8y),'):'
call test(trim(comment),DIM(i4x,i8y))
write(comment,'(a,i0,a,i0,a,i0,a,i0,a)') &
'DIM(',i8x,'_',kind(i8x),',',i4y,'_',kind(i4y),'):'
call test(trim(comment),DIM(i8x,i4y))
write(comment,'(a,f0.1,a,i0,a,f0.1,a,i0,a)') &
'DIM(',r4x,'_',kind(r4x),',',r8y,'_',kind(r8y),'):'
call test(trim(comment),DIM(r4x,r8y))
write(comment,'(a,f0.1,a,i0,a,f0.1,a,i0,a)') &
'DIM(',r8x,'_',kind(r8x),',',r4y,'_',kind(r4y),'):'
call test(trim(comment),DIM(r8x,r4y))
call test3(DIM)
end program test2
subroutine test3(fun)
implicit none
real x, y, fun
x = 11
y = 7
write(*,'(3(a,f0.1))') &
'x = ',x,', y = ',y,', fun(x,y) = ',fun(x,y)
end subroutine test3
C:\gfortran\clf\dimtest>gfortran -Wall test2.f90 -otest2
C:\gfortran\clf\dimtest>test2
DIM(11_4,7_8): Type of variable: INTEGER, Kind = 8, value = 4
DIM(11_8,7_4): Type of variable: INTEGER, Kind = 8, value = 4
DIM(11.0_4,7.0_8): Type of variable: REAL, Kind = 8, value =
4.00000000000000
DIM(11.0_8,7.0_4): Type of variable: REAL, Kind = 8, value =
4.00000000000000
x = 11.0, y = 7.0, fun(x,y) = 4.0
If you fixed the man page to say that variables of the same allowed
type but different kinds could be passed as a gnu extension, that the
kind of the result is the same as the kind of x-y, and that DIM is
itself a specific name, I think it would be clearer. Also, does
gfortran guarantee that KIND(0) = KIND(0.0) = 4 and that
KIND(0.0d0) = 8? If not... Oh, I see now, that's covered in 8.1,
Introduction to Intrinsic Procedures.
> Also DIM is not listed as a specific name there,
> although the compiler does consider it to be one, consistent
> with the standard.
A longer list of specific names omitted in the gfortran manual:
C:\gfortran\clf\dimtest>type test_specific.f90
program test_specific
implicit none
abstract interface
elemental function r1r1(x)
real r1r1
real, intent(in) :: x
end function r1r1
elemental function r2r1(x,y)
real r2r1
real, intent(in) :: x,y
end function r2r1
elemental function r2d1(x,y)
double precision r2d1
real, intent(in) :: x,y
end function r2d1
elemental function c1r1(x)
real c1r1
complex, intent(in) :: x
end function c1r1
elemental function c1c1(x)
complex c1c1
complex, intent(in) :: x
end function c1c1
pure function ch1i1(string)
integer ch1i1
character(*), intent(in) :: string
end function ch1i1
elemental function ch2i1(string,substring)
integer ch2i1
character(*), intent(in) :: string,substring
end function ch2i1
elemental function i2i1(x,y)
integer i2i1
integer, intent(in) :: x, y
end function i2i1
elemental function r1i1(x)
integer r1i1
real, intent(in) :: x
end function r1i1
end interface
procedure(r1r1), pointer :: pr1r1
procedure(r2r1), pointer :: pr2r1
procedure(r2d1), pointer :: pr2d1
procedure(ch1i1), pointer :: pch1i1
procedure(ch2i1), pointer :: pch2i1
procedure(c1r1), pointer :: pc1r1
procedure(c1c1), pointer :: pc1c1
procedure(i2i1), pointer :: pi2i1
procedure(r1i1), pointer :: pr1i1
real x,y
complex c
character(44) string
character(3) substring
integer i,j
pr1r1 => abs
x = -3.14
write(*,'(a,f0.2,a,f0.2)') &
'Testing ABS specific. A = ',x,', ABS(A) = ',pr1r1(x)
pr1r1 => acos
x = -0.866
write(*,'(a,f0.3,a,f0.3)') &
'Testing ACOS specific. X = ',x,', ACOS(X) = ',pr1r1(x)
pc1r1 => aimag
c = (0.577,-3.14)
write(*,'(a,f0.3,",",f0.2,a,f0.2)') &
'Testing AIMAG specific. Z = (',c,'), AIMAG(Z) = ',pc1r1(c)
! pr1r1 => aint
! x = -3.14
! write(*,'(a,f0.2,a,f0.2)') &
! 'Testing AINT specific. A = ',x,', AINT(A) = ',pr1r1(x)
! pr1r1 => anint
! x = -3.14
! write(*,'(a,f0.2,a,f0.2)') &
! 'Testing ANINT specific. A = ',x,', ANINT(A) = ',pr1r1(x)
pr1r1 => asin
x = -0.866
write(*,'(a,f0.3,a,f0.3)') &
'Testing ASIN specific. X = ',x,', ASIN(X) = ',pr1r1(x)
pr1r1 => atan
x = -1.732
write(*,'(a,f0.3,a,f0.3)') &
'Testing ATAN specific. X = ',x,', ATAN(X) = ',pr1r1(x)
pr2r1 => atan2
x = -0.866
y = 0.500
write(*,'(a,f0.3,a,f0.3,a,f0.3)') &
'Testing ATAN2 specific. X = ',x,', Y = ',y, &
', ATAN2(Y,X) = ',pr2r1(y,x)
pc1c1 => conjg
c = (0.577,-3.14)
write(*,'(a,f0.3,",",f0.2,a,f0.3,",",f0.2,a)') &
'Testing CONJG specific. Z = (',c,'), CONJG(Z) = (',pc1c1(c),')'
pr1r1 => cos
x = -3.14
write(*,'(a,f0.2,a,f0.2)') &
'Testing COS specific. X = ',x,', COS(X) = ',pr1r1(x)
pr1r1 => cosh
x = 0.693
write(*,'(a,f0.3,a,f0.3)') &
'Testing COSH specific. X = ',x,', COSH(X) = ',pr1r1(x)
pr2r1 => dim
x = -0.866
y = 0.500
write(*,'(a,f0.3,a,f0.3,a,f0.3)') &
'Testing DIM specific. X = ',x,', Y = ',y, &
', DIM(X,Y) = ',pr2r1(x,y)
pr2d1 => dprod
x = 1.2
y = 3.4
write(*,'(a,f0.1,a,f0.1,a,f0.2)') &
'Testing DPROD specific. X = ',x,', Y = ',y, &
', DPROD(X,Y) = ',pr2d1(x,y)
pr1r1 => exp
x = 0.693
write(*,'(a,f0.3,a,f0.3)') &
'Testing EXP specific. X = ',x,', EXP(X) = ',pr1r1(x)
! pch2i1 => index
! string = 'The quick brown fox jumps over the lazy dog.'
! substring = 'fox'
! write(*,'(5a,i0)') &
! 'Testing INDEX specific. STRING = ',string,', SUBSTRING = ', &
! substring,', INDEX(STRING,SUBSTRING) = ',pch2i1(string,substring)
! pch1i1 => len
! string = 'The quick brown fox jumps over the lazy dog.'
! write(*,'(3a,i0)') &
! 'Testing INDEX specific. STRING = ',string, &
! ', LEN(STRING) = ',pch1i1(string)
pi2i1 => mod
i = 17
j = 7
write(*,'(a,i0,a,i0,a,i0)') &
'Testing MOD specific. A = ',i,', P = ',j, &
', MOD(A,P) = ',pi2i1(i,j)
! pr1i1 => nint
! x = 62.43
! write(*,'(a,f0.2,a,i0)') &
! 'Testing NINT specific. X = ',x,', EXP(X) = ',pr1r1(x)
pr2r1 => sign
x = -0.866
y = -0.500
write(*,'(a,f0.3,a,f0.3,a,f0.3)') &
'Testing SIGN specific. A = ',x,', B = ',y, &
', SIGN(A,B) = ',pr2r1(x,y)
pr1r1 => sin
x = 0.866
write(*,'(a,f0.3,a,f0.3)') &
'Testing SIN specific. X = ',x,', SIN(X) = ',pr1r1(x)
pr1r1 => sinh
x = 0.693
write(*,'(a,f0.3,a,f0.3)') &
'Testing SINH specific. X = ',x,', SINH(X) = ',pr1r1(x)
pr1r1 => sqrt
x = 2.0
write(*,'(a,f0.3,a,f0.3)') &
'Testing SQRT specific. X = ',x,', SQRT(X) = ',pr1r1(x)
pr1r1 => tan
x = 0.785
write(*,'(a,f0.3,a,f0.3)') &
'Testing TAN specific. X = ',x,', TAN(X) = ',pr1r1(x)
pr1r1 => tanh
x = 0.693
write(*,'(a,f0.3,a,f0.3)') &
'Testing TANH specific. X = ',x,', TANH(X) = ',pr1r1(x)
end program test_specific
C:\gfortran\clf\dimtest>gfortran -std=f2003
test_specific.f90 -otest_specific
C:\gfortran\clf\dimtest>test_specific
Testing ABS specific. A = -3.14, ABS(A) = 3.14
Testing ACOS specific. X = -.866, ACOS(X) = 2.618
Testing AIMAG specific. Z = (.577,-3.14), AIMAG(Z) = -3.14
Testing ASIN specific. X = -.866, ASIN(X) = -1.047
Testing ATAN specific. X = -1.732, ATAN(X) = -1.047
Testing ATAN2 specific. X = -.866, Y = .500, ATAN2(Y,X) = 2.618
Testing CONJG specific. Z = (.577,-3.14), CONJG(Z) = (.577,3.14)
Testing COS specific. X = -3.14, COS(X) = -1.00
Testing COSH specific. X = .693, COSH(X) = 1.250
Testing DIM specific. X = -.866, Y = .500, DIM(X,Y) = 0.000
Testing DPROD specific. X = 1.2, Y = 3.4, DPROD(X,Y) = 4.08
Testing EXP specific. X = .693, EXP(X) = 2.000
Testing MOD specific. A = 17, P = 7, MOD(A,P) = 3
Testing SIGN specific. A = -.866, B = -.500, SIGN(A,B) = -.866
Testing SIN specific. X = .866, SIN(X) = .762
Testing SINH specific. X = .693, SINH(X) = .750
Testing SQRT specific. X = 2.000, SQRT(X) = 1.414
Testing TAN specific. X = .785, TAN(X) = .999
Testing TANH specific. X = .693, TANH(X) = .600
Now, the above example leaves me with some questions from the
standard. Firstly, there are some specific procedures that
correspond to generic procedures with an optional KIND= argument
(AINT, ANINT, INDEX, LEN, and NINT). My assumption is that there is
no way to specify an interface where there is an optional KIND=
argument which dictates the KIND of the result. Thus I omit this
argument in my abstract interface, but gfortran rejects my code,
demanding that I include the optional KIND= argument. I claim that
since f03 is supposed to be compatible with F77, and you could pass
these specific procedures as actual arguments to procedures that had
no way of knowing that their dummy procedure arguments had optional
arguments, that the interface without the optional KIND= argument is
the correct one.
Also INDEX has an additional BACK= argument, but the f03 standard
doesn't refer to a LOGICAL dummy argument associated with the INDEX
specific procedure nor does F77 TTBOMK have a BACK= optional dummy
argument. Thus I conclude that the correct interface for the INDEX
specific procedure is as I have given above, but gfortran disagrees.
The gfortran manual also insists that STRING, SUBSTRING, and BACK
(if present) must be scalars, which is not the case.
For an intrinsic procedure to be used as an actual argument, it
must be named in an INTRINSIC statement, but I was surprised to
discover that it need not be for it to be used as a procedure
target. Is this true? Is this consistent?
There were still a few keywords incorrect in the gfortran manual
even though a pass has been made through it to fix them:
C:\gfortran\clf\dimtest>type bad_specific.f90
program bad_specific
implicit none
double precision x
double precision y
integer i
integer j
x = -3.14d0
! write(*,'(a,f0.2,a,f0.2)') &
! 'Testing DINT intrinsic. A = ',x,', DINT(X) = ',dint(A=x)
write(*,'(a,f0.2,a,f0.2)') &
'Testing DINT intrinsic. X = ',x,', DINT(X) = ',dint(x=x)
y = 42.0d0
! write(*,'(a,f0.2,a,f0.2)') &
! 'Testing DSIGN intrinsic. A = ',x,', B = ',y, &
! ', DSIGN(A,P) = ',dsign(A=x,B=y)
write(*,'(a,f0.2,a,f0.2)') &
'Testing DSIGN intrinsic. A = ',x,', P = ',y, &
', DSIGN(A,P) = ',dsign(A=x,P=y)
! write(*,'(a,f0.2,a,i0)') &
! 'Testing IDNINT intrinsic. A = ',x,', IDNINT(X) = ',idnint(A=x)
write(*,'(a,f0.2,a,i0)') &
'Testing IDNINT intrinsic. X = ',x,', IDNINT(X) = ',idnint(X=x)
i = 3
j = -7
! write(*,'(a,i0,a,i0,a,i0)') &
! 'Testing ISIGN intrinsic. A = ',i,', B = ', j, &
! ', ISIGN(A,B) = ',isign(A=i,B=j)
write(*,'(a,i0,a,i0,a,i0)') &
'Testing ISIGN intrinsic. A = ',i,', P = ', j, &
', ISIGN(A,P) = ',isign(A=i,P=j)
end program bad_specific
C:\gfortran\clf\dimtest>gfortran bad_specific.f90 -obad_specific
bad_specific.f90:12.54:
'Testing DINT intrinsic. X = ',x,', DINT(X) = ',dint(x=x)
1
Error: Can't find keyword named 'x' in call to 'dint' at (1)
bad_specific.f90:19.24:
', DSIGN(A,P) = ',dsign(A=x,P=y)
1
Error: Can't find keyword named 'p' in call to 'dsign' at (1)
bad_specific.f90:23.58:
'Testing IDNINT intrinsic. X = ',x,', IDNINT(X) = ',idnint(X=x)
1
Error: Can't find keyword named 'x' in call to 'idnint' at (1)
bad_specific.f90:31.24:
', ISIGN(A,P) = ',isign(A=i,P=j)
1
Error: Can't find keyword named 'p' in call to 'isign' at (1)
Also I see that under the ABS intrinsic, the keywords have been
fixed in the Name column, but not in the Argument column. Didn't
check other functions for this.