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

Extending types and ambiguous interfaces

159 views
Skip to first unread message

Arjen Markus

unread,
Apr 27, 2011, 2:53:08 AM4/27/11
to
Hello,

I am trying to use type extension and I have run into a puzzle that
I am unable to solve. The program below is not quite complete,
I left out some routines, but it illustrates the problem.

I have a type point2d and an extended type point3d. For both I want to
use a function add_vector or an overloaded operation +. This way
I hope my program will be able to transparently use either point2d or
point3d variables and remain completely the same (at least code-wise).

The signatures of the functions are:

function add_vector_2d( point, vector )
class(point2d), intent(in) :: point
class(point2d), intent(in) :: vector
type(point2d) :: add_vector_2d
end function

and

function add_vector_3d( point, vector )
class(point3d), intent(in) :: point
class(point3d), intent(in) :: vector
type(point3d) :: add_vector_3d
end function

With these signatures and a generic interface I get a message that the
interface is ambiguous.

If I change the type for the vector argument to "type(...)", the
ambiguity is resolved, but then the compiler (in my case, gfortran)
complains that the + operation has to work on two class (polymorphic)
variables.

I have tried various possible solutions, but sofar no success.

What is the proper solution? Perhaps I misunderstand the way type
extension and type-bound procedures work and what I want to do is not
possible. In that case I would like to know that ;).

Regards,

Arjen

-------------------------------
! random_walk.f90 --
! Simulate a random walk in two and three dimensions
!
! Problem:
! - with both arguments class(..) add_vector_2d and add_vector_3d
ambiguous
! - with vector type(...) error on operator(+): class(...) actual
arguments
!
module points2d3d

implicit none

type point2d
real :: x, y
contains
procedure :: print => print_2d
procedure :: add_vector => add_vector_2d
generic, public :: operator(+) => add_vector
end type point2d

type, extends(point2d) :: point3d
real :: z
contains
procedure :: print =>
print_3d
procedure :: add_vector_3dversion =>
add_vector_3d
generic, public :: add_vector_new =>
add_vector_3dversion
generic, public :: operator(+) => add_vector_3dversion
end type point3d

contains
subroutine print_2d( point )
class(point2d) :: point

write(*,'(2f10.4)') point%x, point%y
end subroutine print_2d

subroutine print_3d( point )
class(point3d) :: point

write(*,'(3f10.4)') point%x, point%y, point%z
end subroutine print_3d

function add_vector_2d( point, vector )
class(point2d), intent(in) :: point
class(point2d), intent(in) :: vector
type(point2d) :: add_vector_2d

add_vector_2d%x = point%x + vector%x
add_vector_2d%y = point%y + vector%y

end function add_vector_2d

function add_vector_3d( point, vector )
class(point3d), intent(in) :: point
type(point3d), intent(in) :: vector

type(point3d) :: add_vector_3d

add_vector_3d%point2d = point%point2d + vector%point2d
add_vector_3d%z = point%z + vector%z

end function add_vector_3d

end module points2d3d

program random_walk

use points2d3d ! Both 2D and 3D points available

type(point2d), target :: point_2d, vector_2d
type(point3d), target :: point_3d, vector_3d

!
! A variable of class point2d can point to point_2d but
! also to point_3d
!
class(point2d), pointer :: point, vector

integer :: nsteps = 100
integer :: i
integer :: trial
real :: deltt = 0.1

! Select what type of point ...
point => point_2d
vector => vector_2d

do trial = 1,2
if ( trial == 1 ) then
write(*,*) 'Two-dimensional walk:'
else
write(*,*) 'Three-dimensional walk:'
endif

call random_vector( point )

do i = 1,nsteps
call random_vector( vector )

point = point + vector

call print_point( point )
enddo

! Now let's take a 3D walk ...

point => point_3d
vector => vector_3d

enddo
end program random_walk

Simon

unread,
Apr 27, 2011, 4:39:13 AM4/27/11
to

Arjen,

With the current compiler the error seems to be the lack of an
assignment definition:

C:\Documents and Settings\simon>ifort -c t.f90
Intel(R) Visual Fortran Compiler XE for applications running on IA-32,
Version 12.0.3.175 Build 20110309
Copyright (C) 1985-2011 Intel Corporation. All rights reserved.

t.f90(99): error #8304: In an intrinsic assignment statement, variable
shall not be polymorphic. [POINT]


point = point + vector

------------^
compilation aborted for t.f90 (code 1)

Hope that helps,

Simon


Arjen Markus

unread,
Apr 27, 2011, 5:17:43 AM4/27/11
to

Hi Simon,

hm, I do not have Intel Fortran 12.0 available at this moment. Ifort
11.1,
which I can use, does not know the generic keyword yet.

A problem I had before with Ifort was that it did not warn about the
ambiguity and _silently_ used to point2d versions.

I will assemble a more complete program shortly. Could you try that?

Regards,

Arjen

Simon

unread,
Apr 27, 2011, 5:49:33 AM4/27/11
to

Yes - you can post it to me on or off list and I'll give it a try. For
Linux at least you can get the latest (or almost latest) compiler free
for non-commercial use.

Simon

Tobias Burnus

unread,
Apr 27, 2011, 6:38:17 AM4/27/11
to
On Apr 27, 8:53 am, Arjen Markus <arjen.markus...@gmail.com> wrote:
> I have a type point2d and an extended type point3d. For both I want to
> use a function add_vector or an overloaded operation +. This way
> I hope my program will be able to transparently use either point2d or
> point3d variables and remain completely the same (at least code-wise).
>
> With these signatures and a generic interface I get a message that the
> interface is ambiguous.

My feeling is that the program is valid (ignoring the assignment
issue, ifort 12 pointed out). However, I cannot really pinpoint it in
the standard.


In the section "12.5.5.2 Resolving procedure references to names
established to be generic" (F2008), one finds:

"If the reference is consistent with a nonelemental reference to one
of the specific interfaces of a generic interface that has that name
and either is defined in the scoping unit in which the reference
appears or is made accessible by a USE statement in the scoping unit,
the reference is to the specific procedure in the interface block that
provides that interface. The rules in 12.4.3.4.5 ensure that there can
be at most one such specific procedure."

Especially the last two sentences imply that the two procedures are
ambiguous as either provides an interface for any variable with a
declared type of "class(point3d)".


"A dummy argument is type, kind, and rank compatible, or TKR
compatible, with another dummy argument if the first is type
compatible with the second, the kind type parameters of the first have
the same values as the corresponding kind type parameters of the
second, and both have the same rank." (12.4.3.4.5 Restrictions on
generic declarations, F2008)

Here, I am not sure: both functions have different declared types, but
while passing a CLASS(point3d) to CLASS(point2d) is valid, the reverse
isn't. ("A polymorphic entity that is not an unlimited polymorphic
entity is type compatible with entities of the same declared type or
any of its extensions.", cf. "4.3.1.3 CLASS".)


And (12.4.3.4.5 Restrictions on generic declarations):

"Two dummy arguments are distinguishable if [...] they are both data
objects or known to be functions, and neither is TKR compatible with
the other" [...]
C1212 Within the scope of a generic operator, if two procedures with
that identi er have the same number of arguments, one shall have a
dummy argument that corresponds by position in the argument list to a
dummy argument of the other that is distinguishable from it."

I probably should have a closer look at the "neither" and "one shall"
to understand whether
"A compatible to B AND B compatible to A"
or
"A compatible to B OR B compatible to A"
is meant.

Tobias

Arjen Markus

unread,
Apr 28, 2011, 2:41:46 AM4/28/11
to

I have revised the program a bit (with help from Simon) and that has
solved
at least some of the issues. gfortran still complains about the
generic interfaces
causing ambiguities, but I have posted the program on the gfortran
mailing list.

More to follow ...

Regards,

Arjen

Ian Harvey

unread,
May 14, 2011, 10:10:37 PM5/14/11
to
On 28/04/2011 4:41 PM, Arjen Markus wrote:
> On 27 apr, 12:38, Tobias Burnus<bur...@net-b.de> wrote:
...

>> My feeling is that the program is valid (ignoring the assignment
>> issue, ifort 12 pointed out). However, I cannot really pinpoint it in
>> the standard.
...

>> "Two dummy arguments are distinguishable if [...] they are both data
>> objects or known to be functions, and neither is TKR compatible with
>> the other" [...]
>> C1212 Â Within the scope of a generic operator, if two procedures with

>> that identi er have the same number of arguments, one shall have a
>> dummy argument that corresponds by position in the argument list to a
>> dummy argument of the other that is distinguishable from it."
> >> I probably should have a closer look at the "neither" and "one shall"
>> to understand whether
>> "A compatible to B AND B compatible to A"
>> or
>> "A compatible to B OR B compatible to A"
>> is meant.
>>
>> Tobias
>
> I have revised the program a bit (with help from Simon) and that has
> solved
> at least some of the issues. gfortran still complains about the
> generic interfaces
> causing ambiguities, but I have posted the program on the gfortran
> mailing list.
>
> More to follow ...

Did anything more come of this? I ran into the same issue trying to
extend a generic (for an operator) type bound procedure, where in the
extension type I wanted to add a specific function that returned a
non-polymorphic result, as opposed to an allocatable polymorphic result
that was originally in the specific binding in the parent type.

I think that the AND option above is what the standard dictates, so I'm
out of luck. Bit of a shame. I think to get this to work you'd need
some way of restricting the inheritance of generics or some way of
allowing them to be overwritten in extended types based on some sort of
"better match to the declared type of the passed argument" logic.
(Having compile time "templates" in the language could help too). I
guess what I should be doing is simply "overloading" a different (or
creating a new) operator in the extension type.

FWIW ifort 12.0.3 almost does this, once you work around/accept some
compiler bugs related to the abstract interface/type.

MODULE ForExampleSeeTheFollowing
IMPLICIT NONE

TYPE, ABSTRACT :: Parent
CHARACTER(:), ALLOCATABLE :: some_text
CONTAINS
PROCEDURE(parent_Multiply_intf), DEFERRED :: Multiply
! for ifort 12.0.3 comment out above and replace with
! PROCEDURE :: Multiply => parent_Multiply
! or you'll get link time reference to abstract interface.
GENERIC :: OPERATOR(*) => Multiply
END TYPE Parent

ABSTRACT INTERFACE
FUNCTION parent_Multiply_intf(lhs, rhs) RESULT(res)
IMPORT Parent
IMPLICIT NONE
CLASS(Parent), INTENT(IN) :: lhs
REAL, INTENT(IN) :: rhs
! Ideally want to specify that dynamic type of this
! will be the same as lhs. Has to be allocatable
! because Parent is abstract.
CLASS(Parent), ALLOCATABLE :: res
END FUNCTION parent_Multiply_intf
END INTERFACE

TYPE, EXTENDS(Parent) :: Extension
CONTAINS
PROCEDURE :: Multiply => ext_Multiply
PROCEDURE :: Multiply_non_poly => ext_Multiply_non_poly
! Can't do this? Original binding was for a CLASS(Parent)
! argument, this is for CLASS(Extension), which is a
! better compile-time match (passed argument only type
! compatible in one direction).
GENERIC :: OPERATOR(*) => Multiply_non_poly
END TYPE Extension

CONTAINS
! ifort 12.0.3 workaround.
FUNCTION parent_Multiply(lhs, rhs) RESULT(res)
CLASS(Parent), INTENT(IN) :: lhs
REAL, INTENT(IN) :: rhs
CLASS(Parent), ALLOCATABLE :: res
!****
ALLOCATE(Extension:: res)
res%some_text = 'parent_Mutiply'
END FUNCTION parent_Multiply

FUNCTION ext_Multiply(lhs, rhs) RESULT(res)
CLASS(Extension), INTENT(IN) :: lhs
REAL, INTENT(IN) :: rhs
CLASS(Parent), ALLOCATABLE:: res
!****
! Grumble, have to wait for F2008 for polymorphic assignment.
ALLOCATE(res, SOURCE=Extension('ext_Multiply'))
END FUNCTION ext_Multiply

FUNCTION ext_Multiply_non_poly(lhs, rhs) RESULT(res)
CLASS(Extension), INTENT(IN) :: lhs
REAL, INTENT(IN) :: rhs
TYPE(Extension) :: res
!****
res = Extension('ext_Multiply_non_poly')
END FUNCTION ext_Multiply_non_poly

SUBROUTINE Here_an_example_of_desired_usage_and_behaviour
CLASS(Parent), ALLOCATABLE :: a
TYPE(Extension) :: b
!****
ALLOCATE(Extension:: a)
! Lots of allocation/deallocation under the hood,
! would expect it to print "ext_Multiply".
! (ifort prints parent_Multiply to keep us on our toes).
CALL dump(a * 1.0)

! No need for allocation/deallocation,
! would like it to print "ext_Multiply_non_poly"
CALL dump(b * 1.0)
END SUBROUTINE Here_an_example_of_desired_usage_and_behaviour

SUBROUTINE dump(arg)
CLASS(Parent), INTENT(IN) :: arg
PRINT "(A)", arg%some_text
END SUBROUTINE dump
END MODULE ForExampleSeeTheFollowing

PROGRAM Test
USE ForExampleSeeTheFollowing
IMPLICIT NONE
CALL Here_an_example_of_desired_usage_and_behaviour
END PROGRAM Test

Jim Xia

unread,
May 15, 2011, 12:01:21 PM5/15/11
to

This is illegal code. Type extension inherits the operator(*) from
its parent, and yet you declared another operation,
ext_Multiply_non_poly, as an operator(*). So you end up with two
defined operations, ext_Multiply and ext_Multiply_non_poly, as
operator(*). The problem is these two procedures have the same
interfaces, so a call can not be resolved.

Tobias already asked j3 with regard to Ajren's program. His program
suffers a similar problem as yours although slightly different, i.e.
the two overloaded operator are not distinguishable.

Cheers,

Jim

Arjen Markus

unread,
May 18, 2011, 2:49:14 AM5/18/11
to
> Jim- Tekst uit oorspronkelijk bericht niet weergeven -
>
> - Tekst uit oorspronkelijk bericht weergeven -

For the original program I posted I think of a few workarounds - not
tested
yet. But the matter of ambiguous interfaces could be solved, I think,
if
one looks at the more specific type. You can substitute a
class(point3d)
variable for a class(poin2d) one, but not the other way around. In
that
sense there is no ambiguity.

Regards,

Arjen

0 new messages