There is an example in N1601 final draft of F2003 (Annex C.1.7 Generic type-bound procedures, page 445) showing ‘rational_numbers’ module. Oddly, it does not seem to be valid F2003 code, as it contains PROCEDURE statements with more than one procedure name, as in PROCEDURE,PRIVATE :: rat_asgn_i, rat_plus_rat, rat_plus_i
Lists were allowed here only in F2008.
Worse enough, compilation with gfortran 9/10 fails (even if F2008 features are allowed) saying
Error: INTENT(OUT) argument ‘a’ of pure procedure ‘rat_asgn_i’ at (1) may not be polymorphic
According to TECHNICAL CORRIGENDUM 1 N1903
Fortran 2003 permitted an INTENT(OUT) argument of a pure subroutine to be polymorphic; that is not permitted by this part of ISO/IEC 1539.
So, in principle, one should be able to compile this snippet in strict F2003 if there were not the procedure lists (above). That’s not the case with GNU Fortran, as it reports the latter problem as an error even with ‘-std=f2003’ option. The only way to get rid of it is to remove ELEMENTAL attribute from that subroutine which is bad idea from the point of view of the module use.
Apart from the problems with that particular example/compiler. Is it at all possible to write elemental subroutine for assignment to a derived type entity? AFAIK Fortran requires (who-knows-why) the argument being polymorphic (CLASS) and now it forbids it to have INTENT(OUT) atribute. Sort of Paragraph 22 to me.
PS. Excuse my newbiesness if the post gets poorly formatted. I couldn’t find any hints on how to include code into the posts. Nor can I see any PREVIEW button here.
regards, Michal
Your issues with example code toward type-bound procedures in N1601 are valid. Some problem or other persists through the next 2 revisions of the standard, Fortran 2008 and 2018. While errors in the latest revision can be addressed possibly through corrigenda, the prior versions are effectively viewed as “frozen”.
Re: your question on “Is it at all possible to write elemental subroutine for assignment to a derived type entity?”, an option is INTENT(INOUT) for the passed-object dummy argument. Here’s a somewhat easier-to-read revised example of the one in the Appendix of the Fortran draft that you can review to see what the language supports:
module rational_numbers
implicit none
private
type, public :: rational
private
integer :: n = 0
integer :: d = 0
contains
private
! ordinary type-bound procedure
procedure :: real => rat_to_real
! specific type-bound procedures for generic support
procedure :: rat_asgn_i, rat_plus_i
procedure :: rat_plus_rat => rat_plus
procedure, pass(b) :: i_plus_rat
! generic type-bound procedures
generic, public :: assignment(=) => rat_asgn_i
generic, public :: operator(+) => rat_plus_rat, rat_plus_i, i_plus_rat
end type
contains
elemental real function rat_to_real(this) result(r)
class(rational),intent(in) :: this
r = real(this%n)/this%d
end function
elemental subroutine rat_asgn_i(a,b)
class(rational),intent(inout) :: a
integer,intent(in) :: b
a%n = b
a%d = 1
end subroutine
elemental type(rational) function rat_plus_i(a,b) result(r)
class(rational),intent(in) :: a
integer,intent(in) :: b
r%n = a%n + b*a%d
r%d = a%d
end function
elemental type(rational) function i_plus_rat(a,b) result(r)
integer,intent(in) :: a
class(rational),intent(in) :: b
r%n = b%n + a*b%d
r%d = b%d
end function
elemental type(rational) function rat_plus(a,b) result(r)
class(rational),intent(in) :: a,b
r%n = a%n*b%d + b%n*a%d
r%d = a%d * b%d
end function
end module rational_numbers
Thanks for the response. INTENT(INOUT) - that simple ! I blindly assumed that the restriction regards the modifiability of the dummy parameter and so that OUT or INOUT are equally banned. Still I find the solution as a trick which is hardly explicable in terms of what the INTENT attribute should mean. I can see no IN-ness for a dummy parameter which represents the LHS of a Fortran assignment statement. Were it some kind of .INCR. user-defined operator like ++ or += in C, it would be a different story. But surely, I have rather shallow understanding of the polyphorphism in Fortran, so I might be wrong.
Starting with the example in your modified form, I tried to play a bit more with type-bound stuff that is really a new thing to me. The line procedure :: real => rat_to_real
looks like an invitation to overload the intrinsic REAL() function, so I tried to do it like
procedure :: rat_to_real
generic, public :: real => rat_to_real
to no success. I was only able to obtain that in F90/95 way, removing rat_to_real declaration from the type definition and private line from the very beginning of the module and adding an interface outside the type definition
interface real
module procedure rat_to_real
end interface real
I still wonder whether there is a way to do it properly using type-bound procedure/generic.
In F18 (the current, and only non-deleted standard) the example is in C.2.3. In the margin of my paper F03 copy, I have a note that the PROCEDURE statement is not correct for F03. However, you should be concerned about conformance to F18. The F18 standard does. indeed. disallow INTENT(OUT) and polymorphic: “An INTENT (OUT) dummy argument of a pure procedure shall not be polymorphic or have a polymorphic allocatable ultimate component.” A key feature if INTENT(OUT) is that it causes the dummy to become undefined on entry. If that is not important, INTENT(INOUT) is a viable alternative.