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

abstract types

6 views
Skip to first unread message

sfilippone

unread,
Nov 25, 2010, 9:12:17 AM11/25/10
to
Hello
It is my understanding that what I am about to discuss is illegal
(which is somewhat unfortunate), and it gets rejected by two of the
compilers I have (NAG and GNU).
It seems I cannot use an abstract class for this (see below).
Suppose I have an object hierarchy which is composed of a "core" set
of attributes plus variations on some others.
In this case I may have some methods that can be implemented at the
"core" level, and thus could have procedures defiend in the abstract
type, and methods that work at the derived level, and they can be
declared as deferred in the abstract type.

There is however a third possibility: a method whose implementation
may be logically split into a base part and a derived part. A logical
choice to avoid code duplication would be to have the derived method
invoke the parent type method, and then finish off with the specific
details. If the base type is abstract this is forbidden; on the other
hand, if I use a normal base type, then the "derived" methods cannot
be deferred and must have a default implementation at the base level
(typically, just throw an error because the derived class is logically
incomplete), and the derived class is not detected as incomplete until
runtime.

As you see, declaring the incomplete methods as deferred, would be
convenient to avoid coding the base methods, but then the base methods
cannot be invoked from the derived methods, so either way I have some
code duplication. The type of code duplication I would get in this
context is such that i do not normally use abstract types (since with
the second scheme the "additional" code is just the error throwing
part, which is only invoked when things are going wrong, whreas in the
other scheme I would have the "base" method replicated, so that any
change has to be replicated in all of the derived classes).

Am I missing anything? Comments anyone?

Thanks
Salvatore

Wolfgang Kilian

unread,
Nov 25, 2010, 10:02:34 AM11/25/10
to
On 11/25/2010 03:12 PM, sfilippone wrote:
> Hello
> [...]

> There is however a third possibility: a method whose implementation
> may be logically split into a base part and a derived part. A logical
> choice to avoid code duplication would be to have the derived method
> invoke the parent type method, and then finish off with the specific
> details. If the base type is abstract this is forbidden;

Why? For an abstract type, its type-bound procedures may be, but need
not be deferred. You can't have objects of abstract type, but a method
of an extended type can invoke the methods of its base type, abstract or
not.

-- Wolfgang

--
E-mail: firstnameini...@domain.de
Domain: yahoo

sfilippone

unread,
Nov 25, 2010, 10:19:05 AM11/25/10
to
On 25 Nov, 16:02, Wolfgang Kilian <see...@domain.invalid> wrote:
> On 11/25/2010 03:12 PM, sfilippone wrote:
>
> > Hello
> > [...]
> > There is however a third possibility: a method whose implementation
> > may be logically split into a base part and a derived part. A logical
> > choice to avoid code duplication would be to have the derived method
> > invoke the parent type method, and then finish off with the specific
> > details. If the base type is abstract this is forbidden;
>
> Why?  For an abstract type, its type-bound procedures may be, but need
> not be deferred.  You can't have objects of abstract type, but a method
Yes, of course.

> of an extended type can invoke the methods of its base type, abstract or
> not.
I am talking about of a method of an extended type calling THE SAME
METHOD from ITS parent.
This is allowed in a normal type by calling the method on the parent
component, but if that parent component is abstract...

here is what happens

[sfilippo@localhost Test7]$ nagfor -o tryabs tryabs.f03
NAG Fortran Compiler Release 5.3(815),5.2(757)
Extension: tryabs.f03, line 2: ABSTRACT attribute
detected at ,@ABSTRACT
Extension: tryabs.f03, line 4: Type-bound procedure part
detected at CONTAINS@<end-of-statement>
Extension: tryabs.f03, line 10: ABSTRACT interface
detected at <end-of-statement>@ABSTRACT
Extension: tryabs.f03, line 12: IMPORT statement
detected at BASE_TYPE@<end-of-statement>
Extension: tryabs.f03, line 13: CLASS keyword
detected at BASE_TYPE@)
Extension: tryabs.f03, line 20: CLASS keyword
detected at BASE_TYPE@)
Extension: tryabs.f03, line 30: EXTENDS keyword
detected at BASE_TYPE@)
Extension: tryabs.f03, line 31: Empty derived type
detected at <end-of-statement>@CONTAINS
Extension: tryabs.f03, line 31: Type-bound procedure part
detected at CONTAINS@<end-of-statement>
Extension: tryabs.f03, line 39: CLASS keyword
detected at FOO_TYPE@)
Extension: tryabs.f03, line 47: CLASS keyword
detected at FOO_TYPE@)
Error: tryabs.f03, line 41: A%BASE_TYPE is of abstract TYPE(BASE_TYPE)
[NAG Fortran Compiler error termination, 1 error, 11 warnings]
=====================================================================

module base_mod
type, abstract :: base_type
integer :: i
contains
procedure, pass(a) :: setit
procedure(get), deferred, pass(a) :: getit

end type base_type

abstract interface
function get(a) result(val)
import :: base_type
class(base_type), intent (in) :: a
integer :: val
end function get
end interface

contains
subroutine setit(a)
class(base_type), intent (inout) :: a

a%i = 1
end subroutine setit

end module base_mod

module foo_mod
use base_mod

type, extends(base_type) :: foo_type
contains
procedure, pass(a) :: setit => foo_setit
procedure, pass(a) :: getit => foo_getit

end type foo_type
contains

subroutine foo_setit(a)
class(foo_type), intent (inout) :: a

call a%base_type%setit()

a%i = 1 + a%i
end subroutine foo_setit

function foo_getit(a) result(val)
class(foo_type), intent (in) :: a
integer :: val

val = a%i
end function foo_getit

end module foo_mod

program try
use foo_mod
type(foo_type) :: a

call a%setit()
write(*,*) 'Result: ',a%getit()
end program try

Wolfgang Kilian

unread,
Nov 25, 2010, 11:11:07 AM11/25/10
to
On 11/25/2010 04:19 PM, sfilippone wrote:
> On 25 Nov, 16:02, Wolfgang Kilian <see...@domain.invalid> wrote:
>> On 11/25/2010 03:12 PM, sfilippone wrote:
>>
>>> Hello
>>> [...]
>>> There is however a third possibility: a method whose implementation
>>> may be logically split into a base part and a derived part. A logical
>>> choice to avoid code duplication would be to have the derived method
>>> invoke the parent type method, and then finish off with the specific
>>> details. If the base type is abstract this is forbidden;
>>
>> Why? For an abstract type, its type-bound procedures may be, but need
>> not be deferred. You can't have objects of abstract type, but a method
> Yes, of course.
>> of an extended type can invoke the methods of its base type, abstract or
>> not.
> I am talking about of a method of an extended type calling THE SAME
> METHOD from ITS parent.

Me too. I'm also surprised. I don't find a constraint in the standard:
the closest reference is (considering structure components)

C611 If the rightmost part-name is of abstract type, data-ref shall be
polymorphic.

but I read this as referring to data components only, the constraint
doesn't make much sense for type-bound procedure components?

An expert should answer this .. probably I just don't read the standard
correctly.

Tobias Burnus

unread,
Nov 26, 2010, 3:16:39 AM11/26/10
to
On Nov 25, 5:11 pm, Wolfgang Kilian <see...@domain.invalid> wrote:
> C611  If the rightmost part-name is of abstract type, data-ref shall be
> polymorphic.
>
> but I read this as referring to data components only, the constraint
> doesn't make much sense for type-bound procedure components?

It makes sense as one has (in F2008):

R1221 procedure-designator is procedure-name
or proc-component-ref
or data-ref % binding-name

and your quote is a constraint to:

R611 data-ref is part-ref [ % part-ref ] ...

I was a bit unsure, however, whether "polymophic%abstract" is allowed
or not. The right-most part-name is an abstract type; hence the
question is whether "polymorphic%abstract" is still polymorphic. The
answer seems to be: No it is not. (It is kind of obvious, but it
still confused me. I have always problems with data-ref to see which
constraint applies to which part-ref and when does it apply to the
whole object. Thanks to Malcolm Cohen for getting this straight.)


I think one could allow it. However, one then would need to put some
constraint in that then the called type-bound procedure is not
deferred - otherwise, one has a problem ...

Tobias

Wolfgang Kilian

unread,
Nov 26, 2010, 3:54:09 AM11/26/10
to

The situation with the present implementation in compilers is actually
more confusing. I'm referring to gfortran 4.6 as of Nov.01 and nagfor
5.2(756). Sample code is below.

- Both allow for assigning and accessing data components of an abstract
parent type via the parent component.

- Both allow for assigning procedure pointer components of an abstract
parent type via the parent component.

- Only gfortran allows for calling procedure pointer components of an
abstract parent type via the parent component.

- Neither allows for calling type-bound procedure components of an
abstract parent type via the parent component.

Regarding the fact that the parent component is always available in this
situation (there is no object of abstract type created), I think that
all of this should be allowed. Note that the existence of a TBP
(whether it is implemented or deferred) can be checked at compile time.

The standard is normative if it says otherwise, however.

Here is the code:
----------------------------------------------
module types
implicit none

type, abstract :: base_t
integer :: i = 0
procedure(base_write_i), pointer :: write_procptr
contains
procedure :: write_i => base_write_i
end type base_t

type, extends (base_t) :: t
end type t

contains

subroutine base_write_i (obj)
class (base_t), intent(in) :: obj
print *, obj%i
end subroutine base_write_i

end module types

program main
use types
implicit none

type(t) :: obj

print *, "Direct printing"
obj%i = 1
print *, obj%i

print *, "Direct printing via parent"
obj%base_t%i = 2
print *, obj%base_t%i ! This works

print *, "Printing via TBP"
obj%i = 3
call obj%write_i

print *, "Printing via parent TBP"
obj%base_t%i = 4
call obj%base_t%write_i ! This doesn't (nagfor/gfortran)

print *, "Printing via OBP"
obj%i = 5
obj%write_procptr => base_write_i
call obj%write_procptr

print *, "Printing via parent OBP"
obj%base_t%i = 6
obj%base_t%write_procptr => base_write_i ! This works
call obj%base_t%write_procptr ! This doesn't (nagfor)

end program main
-------------------------------------------------

Janus Weil

unread,
Nov 26, 2010, 8:22:57 AM11/26/10
to

> The situation with the present implementation in compilers is actually
> more confusing.  I'm referring to gfortran 4.6 as of Nov.01 and nagfor
> 5.2(756).  Sample code is below.
>
> - Both allow for assigning and accessing data components of an abstract
> parent type via the parent component.
>
> - Both allow for assigning procedure pointer components of an abstract
> parent type via the parent component.
>
> - Only gfortran allows for calling procedure pointer components of an
> abstract parent type via the parent component.

Actually this seems to be a bug in gfortran. In this respect proc-ptr
component calls should be subject to the same limitation as type-bound
procedure calls (i.e. C611 in the F08 standard).

> Regarding the fact that the parent component is always available in this
> situation (there is no object of abstract type created), I think that
> all of this should be allowed.  Note that the existence of a TBP
> (whether it is implemented or deferred) can be checked at compile time.
>
> The standard is normative if it says otherwise, however.

Yes, I agree that it would be possible to implement it. Apparently F08
does in fact forbid it, but maybe the standard committee could
consider allowing it the next revision of the standard ?!?

Cheers,
Janus

Wolfgang Kilian

unread,
Nov 26, 2010, 9:40:17 AM11/26/10
to
On 11/26/2010 09:54 AM, Wolfgang Kilian wrote:
> On 11/26/2010 09:16 AM, Tobias Burnus wrote:
>> On Nov 25, 5:11 pm, Wolfgang Kilian <see...@domain.invalid> wrote:
>>> C611 If the rightmost part-name is of abstract type, data-ref shall be
>>> polymorphic.
>>>
>>> but I read this as referring to data components only, the constraint
>>> doesn't make much sense for type-bound procedure components?
>>
>> It makes sense as one has (in F2008):
>>
>> R1221 procedure-designator is procedure-name
>> or proc-component-ref
>> or data-ref % binding-name
>>
>> and your quote is a constraint to:
>>
>> R611 data-ref is part-ref [ % part-ref ] ...
>>
>> I was a bit unsure, however, whether "polymophic%abstract" is allowed
>> or not. The right-most part-name is an abstract type; hence the
>> question is whether "polymorphic%abstract" is still polymorphic. The
>> answer seems to be: No it is not. (It is kind of obvious, but it
>> still confused me. I have always problems with data-ref to see which
>> constraint applies to which part-ref and when does it apply to the
>> whole object. Thanks to Malcolm Cohen for getting this straight.)

Well - no. We are discussing the case where the rightmost part-ref is a
_component_ or TBP of the abstract type. Examples:

Data component:


> print *, obj%base_t%i ! This works

Procedure pointer component:


> obj%base_t%write_procptr => base_write_i ! This works

> call obj%base_t%write_procptr ! This doesn't work (nagfor)

TBP:
> call obj%base_t%write_i ! This doesn't work (nagfor/gfortran)

The component is not of abstract type. It is of integer type, procedure
pointer, or TBP. So I read it as if no constraint applies and the code
should be conforming. Or is there another constraint specifically for
procedures?

Tobias Burnus

unread,
Nov 26, 2010, 10:49:03 AM11/26/10
to
On Nov 26, 3:40 pm, Wolfgang Kilian <see...@domain.invalid> wrote:
> >>> C611  If the rightmost part-name is of abstract type, data-ref shall be
> >>> polymorphic.
> >>
> >> R1221 procedure-designator is procedure-name
> >>                            or proc-component-ref
> >>                            or data-ref % binding-name
> >> R611 data-ref is part-ref [ % part-ref ] ...
>
> >> I was a bit unsure, however, whether "polymophic%abstract" is allowed
> >> or not. The right-most part-name is an abstract type
>
> Well - no.  We are discussing the case where the rightmost part-ref is a
> _component_ or TBP of the abstract type.  Examples:


The latter is not possible. One has:
CALL data-ref % binding-name
and not
CALL data-ref

> Data component:
> >   print *, obj%base_t%i         ! This works

Here, "obj%base_t%i" is a data-ref - and the right-most part-ref is
"i".


> Procedure pointer component:
> >   obj%base_t%write_procptr => base_write_i    ! This works

Similarly, "obj%base_t%write_procptr" is the data-ref, "write_procptr"
is the right-most part-ref.

Side note: As one cannot override components, "obj%base_t
%write_procptr" and "obj%write_procptr" are really identical -- it
only matters if the type is PASSed, cf. below.

> >   call obj%base_t%write_procptr ! This doesn't work (nagfor)

Here, one has a proc-component-ref, namely:
R739 proc-component-ref is scalar-variable % procedure-component-
name

where a variable can be - via designator etc. - be a data-ref such as
"obj%base_t"; again "base_t" is the right-most part-ref. And
"write_procptr" is the procedure-component-name.

If "base_t" is of abstract type and not polymorphic, it is invalid.
The reason is that the right-most part-ref is passed as actual
argument (unless one uses NOPASS).

> TBP:
> >   call obj%base_t%write_i       ! This doesn't work (nagfor/gfortran)
>
> The component is not of abstract type.

Well, I would claim that "obj%base_t" *is* of abstract type and that
it is not polymorphic. "write_i" is a TBP procedure, however, it is
not part of the data-ref but it is just a binding-name. Therefore,
C611 applies and makes the example invalid (if "base_t" is of abstract
type).

* * *

As written before: There is no technical reason that one could not
relax the constraint; however, on then needs to make at least sure
that one cannot call a deferred procedure.

That's not that easy as it seems. For instance, in general, one may
do:

subroutine set(x)
class(abstract) :: x
call x%deferred_tbp()

as the effective argument "x" won't be ever of abstract type and,
thus, there does not exist any deferred type such that one calls an
overridden "x%deferred_tpb", which is fine.

Alternatively, one could allow derived%abstract%set() - but would then
either need to prohibit calls like above or one had to require that in
that case "derived" and not "derived%abstract" is PASSed as argument
or one had to restrict it to NOPASS TBP. Additionally, derived%abstract
%deferred_tpb itself has to be forbidden.


In any case; if you try that hard to use an abstract type, why do you
make it abstract at the first place?

Tobias

Wolfgang Kilian

unread,
Nov 26, 2010, 11:08:50 AM11/26/10
to
On 11/26/2010 04:49 PM, Tobias Burnus wrote:
> On Nov 26, 3:40 pm, Wolfgang Kilian <see...@domain.invalid> wrote:
>>>>> C611 If the rightmost part-name is of abstract type, data-ref shall be
>>>>> polymorphic.

> In any case; if you try that hard to use an abstract type, why do you


> make it abstract at the first place?
>
> Tobias

Thanks for digging into this, you clarified it. I missed the fact that
the TBP has to pass the object as an actual argument (if PASS applies),
so in theory (maybe not in practice) an object of abstract type is
created on-the-fly. Hence the constraint.

The example showed, at least, that gfortran and nagfor are inconsistent
in the handling of procedure pointer components. As Janus pointed out,
this might be a gfortran bug.

The OP had raised the point: he wants to override a procedure, but the
overriding procedure should call the overridden procedure. This works
only via the parent-type component. However, if there is another
procedure in the parent type which is deferred, the parent type is
necessarily abstract, and the problem arises.

The workaround would be to implement the base-type procedure with a
different name, then it could be called directly.

Ian Harvey

unread,
Nov 26, 2010, 6:14:27 PM11/26/10
to
On 27/11/10 03:08, Wolfgang Kilian wrote:
>
> The OP had raised the point: he wants to override a procedure, but the
> overriding procedure should call the overridden procedure. This works
> only via the parent-type component. However, if there is another
> procedure in the parent type which is deferred, the parent type is
> necessarily abstract, and the problem arises.
>
> The workaround would be to implement the base-type procedure with a
> different name, then it could be called directly.

Or maybe have a grand-parent in the hierarchy (parent to the abstract
type) that is not abstract and that implements the "default" behaviour
for the procedure of interest.

That grand parent type could not access the deferred procedures, because
they not present at that level of type declaration.


Janus Weil

unread,
Nov 28, 2010, 3:31:59 PM11/28/10
to

> >>>>> C611  If the rightmost part-name is of abstract type, data-ref shall be
> >>>>> polymorphic.
> > In any case; if you try that hard to use an abstract type, why do you
> > make it abstract at the first place?
>
> Thanks for digging into this, you clarified it.  I missed the fact that
> the TBP has to pass the object as an actual argument (if PASS applies),
> so in theory (maybe not in practice) an object of abstract type is
> created on-the-fly.  Hence the constraint.
>
> The example showed, at least, that gfortran and nagfor are inconsistent
> in the handling of procedure pointer components.  As Janus pointed out,
> this might be a gfortran bug.

Just for completeness: This bug is known to the GCC bugzilla database
as PR 46662 and I just committed a patch which fixes it on gfortran
trunk. Thanks for reporting this misbehavior ...

Cheers,
Janus

0 new messages