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

Passing an arbitrary number of subroutines as a subroutine argument

43 views
Skip to first unread message

Cyrus

unread,
Nov 10, 2010, 6:39:54 PM11/10/10
to
Hello FORTRAN ninjas,

To advance the discussion of an older post, I would like to pass an
arbitrary number of subroutines as arguments to another subroutine. I
realize that I could have multiple arguments as this toy example below
shows:

program test
implicit none
external sub1,sub2

call testsub(sub1,sub2)

end program test


subroutine testsub(s1,s2)
implicit none
real x,y
interface
subroutine s1(x,y)
real, intent(in):: x
real, intent(out)::y
end subroutine
end interface
interface
subroutine s2(x,y)
real, intent(in):: x
real, intent(out)::y
end subroutine
end interface

!
! Insert Computationally Intensive statements on x and y
!

y=10
x=1

!
! End Computationally Intensive statements on x and y
!

call s1(x,y)
call s2(x,y)

end subroutine testsub

subroutine sub1(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=100+x
print*,'test1',y
end subroutine sub1


subroutine sub2(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=1000+x*y
print*,'test2',y
end subroutine sub2

What I would really like though is to be able to pass in an arbitrary
number of arguments, perhaps as an array or pointer to the subroutine.
Maybe it would look something like:

...
subroutine testsub(s,n)
implicit none
real x,y
integer n ! <== number of subroutines to be passed
! some array s that holds the names of the subroutines to be passed in
integer i ! index variable

do i = 1, n
interface
subroutine s(i)(x,y)
real, intent(in):: x
real, intent(out)::y
end subroutine
end interface
end do
!
! Insert Computationally Intensive statements on x and y
!

y=10
x=1

!
! End Computationally Intensive statements on x and y
!

do i = 1, n
call s(i)(x,y)
end do

end subroutine testsub
...

Obviously this syntax would never work but conceptually hopefully it
makes sense. The subroutines would all have the same type of arguments
(in and out) but they would perform different tasks.

Any thoughts?

Thanks,
Cyrus

James Van Buskirk

unread,
Nov 10, 2010, 7:18:03 PM11/10/10
to
"Cyrus" <cyrusp...@gmail.com> wrote in message
news:87fb8984-d6ce-4c91...@v12g2000vbh.googlegroups.com...

> call testsub(sub1,sub2)

> end program test

> y=10
> x=1

> call s1(x,y)
> call s2(x,y)

> end subroutine testsub

You can't have an array of procedure pointers but you can have an
array of a derived type with a procedure pointer component or an
array of TYPE(C_FUNPTR). Since the latter possibility requires
that you either have a fixed maximum number of the passed procedures
active at any one time or that subroutine testsub has a local
variable which is an array of a derived type with a procedure pointer
component, our example will be one which just goes ahead and passes
the array of the derived type. Many languages pass around arrays of
TYPE(C_FUNPTR) routinely, though.

C:\gfortran\clf\multisub>type multisub.f90
module all_my_subs
implicit none
abstract interface
subroutine all_subs(x,y)


real, intent(in):: x
real, intent(out)::y

end subroutine all_subs
end interface
type has_sub
procedure(all_subs), pointer, NOPASS :: sub
end type has_sub
contains


subroutine testsub(s,n)
implicit none
real x,y
integer n

type(has_sub) s(n)

!
! Insert Computationally Intensive statements on x and y
!

y=10
x=1

!
! End Computationally Intensive statements on x and y
!

call s(1)%sub(x,y)
call s(2)%sub(x,y)

end subroutine testsub
end module all_my_subs

program test
use all_my_subs
implicit none
procedure(all_subs) sub1, sub2
type(has_sub) s(2)

s(1)%sub => sub1
s(2)%sub => sub2
call testsub(s,size(s))

end program test

subroutine sub1(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=100+x
print*,'test1',y
end subroutine sub1

subroutine sub2(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=1000+x*y
print*,'test2',y
end subroutine sub2

C:\gfortran\clf\multisub>gfortran multisub.f90 -omultisub

C:\gfortran\clf\multisub>multisub
test1 101.00000
test2 1101.0000

--
write(*,*) transfer((/17.392111325966148d0,6.5794487871554595D-85, &
6.0134700243160014d-154/),(/'x'/)); end


Richard Maine

unread,
Nov 10, 2010, 7:18:32 PM11/10/10
to
Cyrus <cyrusp...@gmail.com> wrote:

> What I would really like though is to be able to pass in an arbitrary
> number of arguments,

You can't have an arbitrary number of arguments - ever. You can have
multiple arguments, making some of them optional, but there is no way to
specify that the number is arbitrary; you have to specify each of the
possible arguments individually.

> perhaps as an array or pointer to the subroutine.

An array argument is not an multiple arguments. It is a single argument,
even though it might have multiple elements. But I'll grant that as a
terminology quibble for now, assuming that an array would meet your
needs.

Sounds like what you want is procedure pointers. That's the only way you
can get procedure information in anything like an array form. Procedure
pointers are an f2003 feature that might or might not be in whatever
compilers you use. Some compilers have variants of the nonstandard Cray
pointer feature that might do the job, but I do not recommend using
that; it is quite nonportable (even among compilers that support Cray
pointers). I never use Cray pointers myself, partly because I find them
confusing and partly because several of the compilers I use don't
support them, so I can give no further advice along that line.

You can't directly have an array of pointers (procedure pointers of
not), but the "usual" workaround is to make a derived type with a single
pointer component. Than you can have an array of that derived type.

One of my visiting nephews is anxious to watch me "play" something more
interesting than comp.lang.fortran (not a very high standard of
"interesting" for him at age 8), so I'll use that as an excuse to beg
out of doing a code sample. But this gives the direction. Perhaps it
will be enough or perhaps someone else can do a sample.

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

Cyrus

unread,
Nov 10, 2010, 8:09:10 PM11/10/10
to
To James:

Thank you for the example. From what I've been able to find (please
remember my ignorance on the subject, hence I am here asking for
help):

http://publib.boulder.ibm.com/infocenter/comphelp/v111v131/index.jsp?topic=/com.ibm.xlf131.aix.doc/language_ref/abstract_interface.html

the 'abstract interface' is a f2003 language reference which is
incompatible with my compiler of choice. I happen to use DIGITAL
Visual Fortran Standard Edition 6.0.A Copyright 1997-1998 mainly due
to its debugging capabilities. If at all possible, I would rather not
go through the process of working with a different compiler. If the
answer is not possible to achieve with my compiler then I will try
something else.

Given this information is there anything that you can recommend to
circumvent the portability issue for your code example?

Thank you,
Cyrus

Cyrus

unread,
Nov 10, 2010, 8:15:34 PM11/10/10
to
To Richard:

Thank you also for your timely response. It seems that James is on the
right track if I used a different compiler that supported some the
latest implementations of f2003. When you have time I would very much
appreciate a code example or perhaps some references to where I might
find some examples.

Thank you,
Cyrus

Richard Maine

unread,
Nov 10, 2010, 10:51:04 PM11/10/10
to
Cyrus <cyrusp...@gmail.com> wrote:

Well, James' example seems a good one - probably better than I would
have done. (Looks like he posted that one while I was in the middle of
composing my first reply or I'd have pointed to it).

You mentioned that your compiler doesn't support abstract interfaces. If
that were the only problem, it would be easy enough to work around. But
I'd guess that if you have a compiler that doesn't support abstract
interfaces, then odds are that it won't support procedure pointers at
all; the two go largely together, as one often wants to use an abstract
interface to declare a procedure pointer.

If you are really stuck with DVF, I doubt you are going to have any luck
other than perhaps with Cray pointers. While DVF was a fine compiler, it
is getting a little old and is never going to see further development.
Particularly, it won't ever see more f2003 features. I disrecommend Cray
pointers, though, and can't help with them.

James Van Buskirk

unread,
Nov 10, 2010, 11:09:38 PM11/10/10
to
"Cyrus" <cyrusp...@gmail.com> wrote in message
news:99128f6a-8346-4cd4...@k11g2000vbf.googlegroups.com...

> To James:

> http://publib.boulder.ibm.com/infocenter/comphelp/v111v131/index.jsp?topic=/com.ibm.xlf131.aix.doc/language_ref/abstract_interface.html

If you are made of money I suggest you upgrade to ifort; if of flesh,
gfortran is what I mostly use nowadays. To make my example work with
DVF (pre-f2003, even pre-2003!) you would need to convert to Cray
pointers.

C:\gfortran\clf\multisub>type multisub1.f90
module all_my_subs
implicit none


interface
subroutine all_subs(x,y)
real, intent(in):: x
real, intent(out)::y
end subroutine all_subs
end interface

pointer(p_sub, all_subs)


contains
subroutine testsub(s,n)
implicit none
real x,y
integer n

integer(kind(p_sub)) s(n)
integer i

!
! Insert Computationally Intensive statements on x and y
!

y=10
x=1

!
! End Computationally Intensive statements on x and y
!

do i = 1, size(s)
p_sub = s(i)
call all_subs(x,y)
end do

end subroutine testsub
end module all_my_subs

program test
use all_my_subs
implicit none

external sub1, sub2
integer(kind(p_sub)) s(2)

s(1) = loc(sub1)
s(2) = loc(sub2)
call testsub(s,size(s))

end program test

subroutine sub1(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=100+x
print*,'test1',y
end subroutine sub1

subroutine sub2(x,y)
implicit none
real, intent(in):: x
real, intent(out)::y
y=1000+x*y
print*,'test2',y
end subroutine sub2

C:\gfortran\clf\multisub>gfortran -fcray-pointer multisub1.f90 -omultisub1

C:\gfortran\clf\multisub>multisub1
test1 101.00000
test2 1101.0000

Having given a Cray pointer example, which was not standard, we might
as well give a C_FUNPTR example:

C:\gfortran\clf\multisub>type multisub2.f90


module all_my_subs
implicit none
abstract interface

subroutine all_subs(x,y) bind(C)
use ISO_C_BINDING


implicit none
real, intent(in):: x
real, intent(out)::y

end subroutine all_subs
end interface

contains
subroutine testsub(s,n)
use ISO_C_BINDING


implicit none
real x,y
integer n

type(C_FUNPTR) s(n)
integer i
procedure(all_subs), pointer :: fptr

!
! Insert Computationally Intensive statements on x and y
!

y=10
x=1

!
! End Computationally Intensive statements on x and y
!

do i = 1, size(s)
call C_F_PROCPOINTER(s(i), fptr)
call fptr(x,y)
end do

end subroutine testsub
end module all_my_subs

program test
use all_my_subs
use ISO_C_BINDING


implicit none
procedure(all_subs) sub1, sub2

type(C_FUNPTR) s(2)

s(1) = C_FUNLOC(sub1)
s(2) = C_FUNLOC(sub2)
call testsub(s,size(s))

end program test

subroutine sub1(x,y) bind(C)


implicit none
real, intent(in):: x
real, intent(out)::y
y=100+x
print*,'test1',y
end subroutine sub1

subroutine sub2(x,y) bind(C)


implicit none
real, intent(in):: x
real, intent(out)::y
y=1000+x*y
print*,'test2',y
end subroutine sub2

C:\gfortran\clf\multisub>gfortran multisub2.f90 -omultisub2
multisub2.f90:4.27:

subroutine all_subs(x,y) bind(C)
1
Warning: Variable 'x' at (1) is a parameter to the BIND(C) procedure
'all_subs'
but may not be C interoperable
multisub2.f90:4.29:

subroutine all_subs(x,y) bind(C)
1
Warning: Variable 'y' at (1) is a parameter to the BIND(C) procedure
'all_subs'
but may not be C interoperable
multisub2.f90:47.19:

s(1) = C_FUNLOC(sub1)
1
Error: Parameter 'sub1' to 'c_funloc' at (1) must be BIND(C)
multisub2.f90:48.19:

s(2) = C_FUNLOC(sub2)
1
Error: Parameter 'sub2' to 'c_funloc' at (1) must be BIND(C)
multisub2.f90:53:

subroutine sub1(x,y) bind(C)
1
Internal Error at (1):
gfc_undo_symbols(): Negative refs

In the above I don't see why gfortran complains that x and y
may not be C interoperable. After all, isn't KIND(1.0) == C_FLOAT?
And if I declare x and y as REAL(C_FLOAT) gfortran stops complaining.

I just don't get the errors about sub1 and sub2 needing to be
BIND(C). Didn't I declare them to be so via the interface block:

abstract interface
subroutine all_subs(x,y) bind(C)
use ISO_C_BINDING


implicit none
real, intent(in):: x
real, intent(out)::y

end subroutine all_subs
end interface

and the PROCEDURE statement:

procedure(all_subs) sub1, sub2
? I'm just trying to follow the example in N1723.pdf, section C.9.3.

Maybe it's too late and I'm too tired, but I don't get it.

Cyrus

unread,
Nov 11, 2010, 1:24:11 PM11/11/10
to
To James and Richard:

This is certainly helpful information. I'm going to see what I can do
about getting a more recent compiler and go from there. James, you
mentioned that you were pulling examples from N1723.pdf, section C.
9.3. Would you mind elaborating on the reference that you are speaking
of? I'd like to take a look and learn some more.

Thanks,
Cyrus

Janus Weil

unread,
Nov 11, 2010, 2:05:10 PM11/11/10
to
On Nov 11, 5:09 am, "James Van Buskirk" <not_va...@comcast.net> wrote:
> Having given a Cray pointer example, which was not standard, we might
> as well give a C_FUNPTR example:
>
> [...]

>
> C:\gfortran\clf\multisub>gfortran multisub2.f90 -omultisub2
> multisub2.f90:4.27:
>
>       subroutine all_subs(x,y) bind(C)
>                            1
> Warning: Variable 'x' at (1) is a parameter to the BIND(C) procedure
> 'all_subs'
> but may not be C interoperable
> [...]

> multisub2.f90:47.19:
>
>    s(1) = C_FUNLOC(sub1)
>                    1
> Error: Parameter 'sub1' to 'c_funloc' at (1) must be BIND(C)
> [...]

>
> In the above I don't see why gfortran complains that x and y
> may not be C interoperable.  After all, isn't KIND(1.0) == C_FLOAT?
> And if I declare x and y as REAL(C_FLOAT) gfortran stops complaining.

I think you're required to explicitly specify the C_FLOAT kind.


> I just don't get the errors about sub1 and sub2 needing to be
> BIND(C).  Didn't I declare them to be so via the interface block:
>
>    abstract interface
>       subroutine all_subs(x,y) bind(C)
>       use ISO_C_BINDING
>       implicit none
>       real, intent(in):: x
>       real, intent(out)::y
>       end subroutine all_subs
>    end  interface
>
> and the PROCEDURE statement:
>
>    procedure(all_subs) sub1, sub2
> ?

Yes, you're right. This is clearly a gfortran bug. But fortunately it
is easily fixed. I already have a patch to cure it, and I'll make sure
it lands on the gfortran trunk very soon.

Cheers,
Janus

James Van Buskirk

unread,
Nov 11, 2010, 2:48:21 PM11/11/10
to
"Cyrus" <cyrusp...@gmail.com> wrote in message
news:17ceb46e-5834-48b8...@o11g2000prf.googlegroups.com...

gfortran and g95 are free. Is there a search engine out there that
doesn't find N1723.pdf on the first try?

James Van Buskirk

unread,
Nov 11, 2010, 2:55:32 PM11/11/10
to
"James Van Buskirk" <not_...@comcast.net> wrote in message
news:ibhha9$ut1$1...@news.eternal-september.org...

> gfortran and g95 are free. Is there a search engine out there that
> doesn't find N1723.pdf on the first try?

Sorry I forgot to mention that N1723.pdf is a draft standard for
the Fortran 2008 standard. Fortran 2003 would be more like N1601.pdf.

James Van Buskirk

unread,
Nov 11, 2010, 3:36:13 PM11/11/10
to
"Janus Weil" <jayd...@googlemail.com> wrote in message
news:f00014dc-0fdd-4f65...@y31g2000vbt.googlegroups.com...

> On Nov 11, 5:09 am, "James Van Buskirk" <not_va...@comcast.net> wrote:

> > subroutine all_subs(x,y) bind(C)
> > 1
> > Warning: Variable 'x' at (1) is a parameter to the BIND(C) procedure
> > 'all_subs'
> > but may not be C interoperable
> > [...]
> > multisub2.f90:47.19:

> > In the above I don't see why gfortran complains that x and y


> > may not be C interoperable. After all, isn't KIND(1.0) == C_FLOAT?
> > And if I declare x and y as REAL(C_FLOAT) gfortran stops complaining.

> I think you're required to explicitly specify the C_FLOAT kind.

I couldn't find that in the standard. I tried a couple of experiments
just now, and with:

real(k), intent(in) ::x

gfortran warns if k is defined as:

integer, parameter :: k = kind(1.0)

but not if defined as:

USE ISO_C_BINDING
integer, parameter :: k = C_FLOAT

also I get a warning for:

integer, parameter :: C_DOUBLE = kind(1.0)
real(C_DOUBLE), intent(in) :: x

but not for:

use ISO_C_BINDING, only: C_FLOAT
integer, parameter :: C_DOUBLE = C_FLOAT
real(C_DOUBLE), intent(in) :: x

I couldn't find a requirement in the standard although I might
not have been looking hard enough. Maybe someone thought that
getting the KIND parameters wrong caused problems often enough
that such a pedantic warning was advisable.

If you want to keep this warning, please note this inconsistency:
gfortran warns for:

character x

and for:

character(1) x

but not for:

character(C_CHAR) x

And to my mind this is the scariest case: where the programmer
has not specified the KIND of x but has erroneously specified
its LEN! I see this all the time and even still make the error
myself. Even so, this is harmless because LEN(x) is required by
the standard to be 1 and C_CHAR is defined by gfortran to be 1 as
well, unless the switch -fgarble-kinds is specified (just kidding).

> > I just don't get the errors about sub1 and sub2 needing to be
> > BIND(C). Didn't I declare them to be so via the interface block:

> > abstract interface
> > subroutine all_subs(x,y) bind(C)
> > use ISO_C_BINDING
> > implicit none
> > real, intent(in):: x
> > real, intent(out)::y
> > end subroutine all_subs
> > end interface

> > and the PROCEDURE statement:

> > procedure(all_subs) sub1, sub2
> > ?

> Yes, you're right. This is clearly a gfortran bug. But fortunately it
> is easily fixed. I already have a patch to cure it, and I'll make sure
> it lands on the gfortran trunk very soon.

Cool. Thank you and team gfortran so much for this.

Janus Weil

unread,
Nov 11, 2010, 4:55:23 PM11/11/10
to

> gfortran and g95 are free.  Is there a search engine out there that
> doesn't find N1723.pdf on the first try?

Note that g95 seems to reject all the three of your examples. The
first one with a syntax error, the second one with 'Unexpected array
reference' and the third one with a segfault. So gfortran seems to be
the only 'free' option here.

Cheers,
Janus

Janus Weil

unread,
Nov 11, 2010, 5:10:06 PM11/11/10
to

That's exactly the behavior I would expect ...


> I couldn't find a requirement in the standard although I might
> not have been looking hard enough.  Maybe someone thought that
> getting the KIND parameters wrong caused problems often enough
> that such a pedantic warning was advisable.

Well, chapter 15.3.2 in the F03 standard states pretty clearly that
only those variables of intrinsic type are interoperable, whose kind
type parameter corresponds to one of the named constants which the
ISO_C_BINDING module defines for this purpose. It does *not*
explicitly give the value of these constants.


> If you want to keep this warning, please note this inconsistency:
> gfortran warns for:
>
>          character x
>
> and for:
>
>          character(1) x
>
> but not for:
>
>          character(C_CHAR) x
>
> And to my mind this is the scariest case: where the programmer
> has not specified the KIND of x but has erroneously specified
> its LEN!  I see this all the time and even still make the error
> myself.  Even so, this is harmless because LEN(x) is required by
> the standard to be 1 and C_CHAR is defined by gfortran to be 1 as
> well

And for the same reason this is not an inconsistency. I think the
compiler does exactly the right thing here.


Btw, I have just committed the fix for the gfortran bug you
discovered.

Cheers,
Janus

Tobias Burnus

unread,
Nov 11, 2010, 5:13:02 PM11/11/10
to

The N... documents refer to WG5 documents such as for Fortran and for C.

My usual reference for Fortran is the webpage at
http://gcc.gnu.org/wiki/GFortranStandards
which contains the links to the Fortran standards (and a bit more).

For Fortran it points (among direct links) to http://www.nag.co.uk/SC22WG5/

For C the page refers to http://www.open-std.org/JTC1/SC22/WG14/

In either case, you find the last standard if you click on "Standards"
at the top of the page.

Regarding N1723.pdf: That's an older version of a draft of the Fortran
2008 standard. You should use N1830 which is the FDIS draft and
virtually identically with the published ISO Fortran 1539-1:2010
standard (which was published in October).

Tobias

Richard Maine

unread,
Nov 11, 2010, 8:41:54 PM11/11/10
to
James Van Buskirk <not_...@comcast.net> wrote:

> "Janus Weil" <jayd...@googlemail.com> wrote in message
> news:f00014dc-0fdd-4f65...@y31g2000vbt.googlegroups.com...

> > I think you're required to explicitly specify the C_FLOAT kind.


>
> I couldn't find that in the standard.

It would shock me if you could find such a requirement because it would
be completely foreign to multiple relevant concepts.

A type parameter value is an integer - that is all. There is absolutely
nothing special about the integer. Kind parameter values do have to be
specified by initalization expressions, but as long as it is an
initialization expression and gives the appropriate value, then you can
do it. Making it portable is another matter.

C_FLOAT is an integer named constant. Again, there is nothing special
about it. It is an integer just like any other.

No, there is no "magic" that somehow links the particular named constant
C_FLOAT to being the only way to specify the kind in question. That just
happens to be a way that the standard portably provides to get a value
that is guaranteed to be the right one.

It is certainly recommended that one use C_FLOAT, but that is not a
requirement of the standard. If a compiler requires that you actually
use the C_FLOAT named constant, then it is just broken.

For a somewhat silly example, if you use (C_FLOAT+C_FLOAT)/2 as the kind
parameter value, that is guaranteed to work (ok, I suppose it isn't
quite guaranteed, but only because theoretically, C_FLOAT could be large
enough that C_FLOAT+C_FLOAT overflowed; that's the only way I see that
it could go wrong). I can't imagine why anyone would want to express it
that way, but if they do, it had better work.

For a slightly more realistic example, I could imagine the possibility
that some code might use a user-defined parameter, say MY_FLOAT, which
was defined to have the same value as C_FLOAT. There could be reasons to
do things like that. A compiler better allow it.

glen herrmannsfeldt

unread,
Nov 11, 2010, 9:53:59 PM11/11/10
to
Richard Maine <nos...@see.signature> wrote:
> James Van Buskirk <not_...@comcast.net> wrote:
>> "Janus Weil" <jayd...@googlemail.com> wrote in message
>> news:f00014dc-0fdd-4f65...@y31g2000vbt.googlegroups.com...

>> > I think you're required to explicitly specify the C_FLOAT kind.

>> I couldn't find that in the standard.

> It would shock me if you could find such a requirement because
> it would be completely foreign to multiple relevant concepts.

But is it required that C_FLOAT be the same as KIND(1.0) when
the underlying data representation is the same?

It is, obviously, non-portable to make the assumption that
the representations are the same, but usually they are.

I could imagine on VAX one being D_FLOAT and the other G_FLOAT,
but otherwise they are likely the same.

If the KIND values were different, then the compiler could
detect the use of KIND(1.0) instead of C_FLOAT (or an expression
that evaluates to C_FLOAT), and issue a diagnostic message.

-- glen


Richard Maine

unread,
Nov 11, 2010, 10:14:28 PM11/11/10
to
glen herrmannsfeldt <g...@ugcs.caltech.edu> wrote:

> Richard Maine <nos...@see.signature> wrote:
> > James Van Buskirk <not_...@comcast.net> wrote:
> >> "Janus Weil" <jayd...@googlemail.com> wrote in message
> >> news:f00014dc-0fdd-4f65...@y31g2000vbt.googlegroups.com...
>
> >> > I think you're required to explicitly specify the C_FLOAT kind.
>
> >> I couldn't find that in the standard.
>
> > It would shock me if you could find such a requirement because
> > it would be completely foreign to multiple relevant concepts.
>
> But is it required that C_FLOAT be the same as KIND(1.0) when
> the underlying data representation is the same?

No, but that was not the question at hand; nor does it have any
relevance to it. The statement I responded to was, as quoted above "I


think you're required to explicitly specify the C_FLOAT kind."

You are not required to explicitly specify the C_FLOAT kind. Period. You
are required to get the kind value correct; that is all. As long as you
end up with the correct value, you can get it by any method you like,
including divine inspiration. The default kind could well be (and most
often is) the correct one.

Portability is, again, a different question. So is recommended practice.
The statement was about a postulated requirement of the standard - not
about portability or recommended practice. Or anyway, that's sure how it
read to me.

And unless I am mistaken (which I suppose I could be) the compiler that
rejected the code did not have any of the speculated (in the part I
elided) properties of unusual kind numbers. It was therefore, in error
to reject the code. I didn't actually study the code well enough to make
sure that this was what was going on, but regardless of that, the
particular statement that I responded to, quoted above, was incorrect.

One could branch off onto all kinds of other questions with little
relationship other than that they relate to kind values. While it is
tempting to give a list of simillarly irrelevant questions, I think I'll
resist. (It was a close call.)

glen herrmannsfeldt

unread,
Nov 12, 2010, 12:19:58 AM11/12/10
to
Richard Maine <nos...@see.signature> wrote:
(snip, I wrote)

>> But is it required that C_FLOAT be the same as KIND(1.0) when
>> the underlying data representation is the same?

> No, but that was not the question at hand; nor does it have any
> relevance to it. The statement I responded to was, as quoted above "I
> think you're required to explicitly specify the C_FLOAT kind."

Looking back at James' examples, they are consistent with
C_FLOAT having a different value from KIND(1.0), and not
with the requirement for the c_FLOAT token.

That isn't obvious from the words, but only from the code samples.

> You are not required to explicitly specify the C_FLOAT kind. Period. You
> are required to get the kind value correct; that is all. As long as you
> end up with the correct value, you can get it by any method you like,
> including divine inspiration. The default kind could well be (and most
> often is) the correct one.

(snip)

> And unless I am mistaken (which I suppose I could be) the compiler that
> rejected the code did not have any of the speculated (in the part I
> elided) properties of unusual kind numbers. It was therefore, in error
> to reject the code. I didn't actually study the code well enough to make
> sure that this was what was going on, but regardless of that, the
> particular statement that I responded to, quoted above, was incorrect.

I thought it was only a warning, so it didn't actually reject
the code.


> One could branch off onto all kinds of other questions with little
> relationship other than that they relate to kind values. While it is
> tempting to give a list of simillarly irrelevant questions, I think I'll
> resist. (It was a close call.)

I was close to some other KIND questions, too.

-- glen

Richard Maine

unread,
Nov 12, 2010, 1:45:47 AM11/12/10
to
glen herrmannsfeldt <g...@ugcs.caltech.edu> wrote:

> Richard Maine <nos...@see.signature> wrote:
> (snip, I wrote)
>
> >> But is it required that C_FLOAT be the same as KIND(1.0) when
> >> the underlying data representation is the same?
>
> > No, but that was not the question at hand; nor does it have any
> > relevance to it. The statement I responded to was, as quoted above "I
> > think you're required to explicitly specify the C_FLOAT kind."
>
> Looking back at James' examples, they are consistent with
> C_FLOAT having a different value from KIND(1.0), and not
> with the requirement for the c_FLOAT token.

While the code results look consistent with that, as I said before, it
would surprise me if that were so. It is certainly possible, but it
would at least slightly surprise me.

Ok. Guess it is time to try an install of gfortran on this machine. It's
been a long time since I tried gfortran (quite a bit longer than I've
had this machine).......

That went easily enough. And running the program

program kinds
use ISO_C_BINDING
write (*,*) C_FLOAT, kind(0.0)
end

gives the result

4 4

which seems to verify my suspicion. Admitedly, it isn't quite proof
because James is presumably running on a different platform than I am,
so the kind numbers *COULD* be different, but my crystal ball says not.
I'll go with my crystal ball instead of your suggestion of what you
mention as being consistent with the data.

Well, let's test further. I just copied James's code to my machine and
tried compiling it. I got the same errors that James did. I'd say that
now is proof.

And I also maintain that the message is just plain wrong. True it is
only a warning; guess I did miss that part before. But it is an
incorrect warning. It says,

"Variable 'x' at (1) is a parameter to the BIND(C) procedure 'all_subs'
but may not be C interoperable"

which is wrong. The variable *IS* C interoperable. True that for the
same code compiled on some other theoretical and probably non-existant
compiler, x might not be interoperable, but the warning doesn't say that
it is about how the code might behave on some other theoretical
compiler. If that's what it is trying to say, it does so very poorly.

While I'm bitching about the warning message, users misuse Fortran
terminology often enough without being encouraged by the compiler's
messages. No, X is not a parameter. It is a dummy argument. Yes, I'm
aware that simillar things in other languages might be called
parameters. But Fortran compilers should use Fortran terminology rather
than that of some other language. Fortran does have parameters, and they
are something entirely unrelated. I personally dislike Fortran's usage
of the term "parameter", but I'm about 3 decades too late in having
input on that.

James Van Buskirk

unread,
Nov 15, 2010, 8:04:41 PM11/15/10
to
"Janus Weil" <jayd...@googlemail.com> wrote in message
news:08109e22-9deb-4f49...@i41g2000vbn.googlegroups.com...

> > real(k), intent(in) ::x

> > but not for:

OK, at least there is a pattern of consistency above.

> > I couldn't find a requirement in the standard although I might
> > not have been looking hard enough. Maybe someone thought that
> > getting the KIND parameters wrong caused problems often enough
> > that such a pedantic warning was advisable.

> Well, chapter 15.3.2 in the F03 standard states pretty clearly that
> only those variables of intrinsic type are interoperable, whose kind
> type parameter corresponds to one of the named constants which the
> ISO_C_BINDING module defines for this purpose. It does *not*
> explicitly give the value of these constants.

> > If you want to keep this warning, please note this inconsistency:
> > gfortran warns for:

> > character x

> > and for:

> > character(1) x

> > but not for:

> > character(C_CHAR) x

> > And to my mind this is the scariest case: where the programmer
> > has not specified the KIND of x but has erroneously specified
> > its LEN! I see this all the time and even still make the error
> > myself. Even so, this is harmless because LEN(x) is required by
> > the standard to be 1 and C_CHAR is defined by gfortran to be 1 as
> > well

> And for the same reason this is not an inconsistency. I think the
> compiler does exactly the right thing here.

I have taken the time to attempt to better articulate my perception
of inconsistency.

First example shows how gfortran rejects default character kind in derived
type:

C:\gfortran\clf\char_warn>type test1.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test1.f90
test1.f90:7.20:

character item
1
Warning: Component 'item' in derived type 't' at (1) may not be C
interoperable,
even though derived type 't' is BIND(C)

Here is the example again that I don't think should prevent the warning:

C:\gfortran\clf\char_warn>type test2.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(C_CHAR) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test2.f90

No errors no warnings! But according to N1839.pdf, section 4.4.3.2, this
is directly equivalent to:

C:\gfortran\clf\char_warn>type test3.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(len=C_CHAR,kind=kind('A')) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test3.f90
test3.f90:7.47:

character(len=C_CHAR,kind=kind('A')) item
1
Warning: Component 'item' in derived type 't' at (1) may not be C
interoperable,
even though derived type 't' is BIND(C)

Which does give the warning. My belief is that it's consistent with the
other stuff gfortran does to warn for test3.f90 therefore it should warn
for the equivalent test2.f90.

gfortran is clever enough to trace back the kind parameter back to C_CHAR
in:

C:\gfortran\clf\char_warn>type test4.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
integer, parameter :: k = C_CHAR
type, bind(C) :: T
character(len=1,kind=k) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test4.f90

but not in:

C:\gfortran\clf\char_warn>type test5.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(len=1,kind=kind(C_CHAR_'A')) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test5.f90
test5.f90:7.49:

character(len=1,kind=kind(C_CHAR_'A')) item
1
Warning: Component 'item' in derived type 't' at (1) may not be C
interoperable,
even though derived type 't' is BIND(C)

A couple of other ways to specify the LEN but not the KIND:

C:\gfortran\clf\char_warn>type test6.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character*(C_CHAR), item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test6.f90

C:\gfortran\clf\char_warn>type test7.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character item*(C_CHAR)
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test7.f90
test7.f90:7.29:

character item*(C_CHAR)
1
Warning: Component 'item' in derived type 't' at (1) may not be C
interoperable,
even though derived type 't' is BIND(C)
C:\gfortran\clf\char_warn>type test8.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(len=C_CHAR) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test8.f90

So we see that the warning is suppressed if the length-selector C_CHAR
goes with the CHARACTER keyword if there is no contradictory KIND
specified, but not if it is a *char-lenth appended to an object-name.
Let's try to abuse gfortran taking this information into account:

C:\gfortran\clf\char_warn>type test9.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(len=2,kind=C_CHAR) item
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test9.f90

C:\gfortran\clf\char_warn>type test10.f90
module mytypes
use ISO_C_BINDING
implicit none
private
public T
type, bind(C) :: T
character(len=*,kind=C_CHAR) item*(2)
end type T
end module mytypes

C:\gfortran\clf\char_warn>gfortran -c test10.f90

So gfortran is missing that item is not interoperable because N1830.pdf,
section 15.3.2 says:

"Table 15.2 shows the interoperability between Fortran intrinsic types
and C types. A Fortran intrinsic type with particular type parameter
values is interoperable with a C type if the type and kind type parameter
value are listed in the table on the same row as that C type. If the type
is character, the length type parameter is interoperable if and only if
its value is one."

So this violates section 15.3.4 C1505:

"C1505 (R425) Each component of a derived type with the BIND attribute
shall be a nonpointer, nonallocatable data component with interoperable
type and type parameters."

What I think would be consistent is:

test1 warn
test2 warn
test3 warn
test4 silent
test5 silent
test6 warn
test7 warn
test8 warn
test9 error
test10 error

In agreement with Richard, I don't like the fact that the warning is
printed by default and not requiring -Wall or -Wpedantic or something
like that, but that's a design decision that you guys make. But I do
think it should be consistent as I recommend in test1.f90:test8.f90 above
and that test9.f90 and test10.f90 should be stigmatized as standards
violations.

> Btw, I have just committed the fix for the gfortran bug you
> discovered.

Thank you for the patch.

0 new messages