How to avoid multiple type definitions due to different kinds?

Since I don’t want to lose gfortran support and gfortran still has the known problem with parameterized type-bound procedures (see: 82943 – [F03] Error with type-bound procedure of parametrized derived type), I defined the needed derived types for different kinds.

So far it works, but after many years I noticed that the modules and submodules are very large because the different types are defined multiple times just because they have different kinds.

Here is an example that I have used so far:

     TYPE :: TYP_REL4
         REAL(KIND=4), ALLOCATABLE, DIMENSION(:, :) :: value
     CONTAINS
         PROCEDURE :: PRC1 => PRC1_REL4
         PROCEDURE :: PRC2 => PRC2_REL4
         PROCEDURE :: PRC3 => PRC3_REL4
     END TYPE TYP_REL4
     
     TYPE :: TYP_REL8
         REAL(KIND=8), ALLOCATABLE, DIMENSION(:, :) :: value
     CONTAINS
         PROCEDURE :: PRC1 => PRC1_REL8
         PROCEDURE :: PRC2 => PRC2_REL8
         PROCEDURE :: PRC3 => PRC3_REL8
     END TYPE TYP_REL8

     
     TYPE :: TYP_REL10
         REAL(KIND=10), ALLOCATABLE, DIMENSION(:, :) :: value
     CONTAINS
         PROCEDURE :: PRC1 => PRC1_REL10
         PROCEDURE :: PRC2 => PRC2_REL10
         PROCEDURE :: PRC3 => PRC3_REL10
     END TYPE TYP_REL10


     TYPE :: TYP_REL16
         REAL(KIND=16), ALLOCATABLE, DIMENSION(:, :) :: value
     CONTAINS
         PROCEDURE :: PRC1 => PRC1_REL16
         PROCEDURE :: PRC2 => PRC2_REL16
         PROCEDURE :: PRC3 => PRC3_REL16
     END TYPE TYP_REL16

Using PDT this example can be reduced like this:

    TYPE :: TYP_REL(K)
    INTEGER, KIND :: K = 8
    REAL(KIND=K), ALLOCATABLE, DIMENSION(:, :) :: value
    CONTAINS
         PROCEDURE :: PRC1 => PRC1_REL
         PROCEDURE :: PRC2 => PRC2_REL
         PROCEDURE :: PRC3 => PRC3_REL
    END TYPE TYP_REL

What would you suggest to avoid multiple type definitions in this situation?

Thanks
Ali

2 Likes

With the PDT version of @Ali’s code and a trivial main program unit:

code snippet
module typ_rel
  type :: typ_r(k)
    integer, kind :: K = 8
    real(kind=k), allocatable, dimension(:, :) :: value
  contains
    procedure :: prc1 => prc1_rel
  end type typ_r
contains
  subroutine prc1_rel(this)
    class(typ_r) :: this
    print *, this%k
  end subroutine prc1_rel
end module typ_rel

program main
  use typ_rel
  implicit none
  integer :: istat
  character(len=80) :: msg
  type (typ_r) :: r8
  type (typ_r(16)) :: r16

  allocate(r8%value(10,10), stat=istat, errmsg=msg, source=8.0_8)
  if ( istat /= 0 ) stop msg
  allocate(r16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
  if ( istat /= 0 ) stop msg
  call r8%prc1
!    call r16%prc1
  print *, shape(r8%value), shape(r16%value), r8%value(1,1), r16%value(1,1)
end program main

I am getting trouble to compile with ifort (gfortran fails totally on the module code). As it is above, it works but when I uncomment the call r16%prc line, ifort complains:

pdt2.f90(29): error #6633: The type of the actual argument differs from the type of the dummy argument.   [R16]
    call r16%prc1
---------^

Any hints how should one construct procedures operating on PDT types?

Thanks @msz59 for your reply.

Using interface procedure it is possible, but I am looking for other possibilities.

MODULE MOD_REL

   TYPE :: TYP_REL(k)
      INTEGER, KIND :: k = 8
      REAL(KIND=k), ALLOCATABLE, DIMENSION(:, :) :: value
   END TYPE TYP_REL


INTERFACE PRC1
  MODULE PROCEDURE PRC1_REL8
  MODULE PROCEDURE PRC1_REL16
END INTERFACE PRC1



CONTAINS

    SUBROUTINE PRC1_REL8(this)
        CLASS(TYP_REL(k=8)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL8


    SUBROUTINE PRC1_REL16(this)
        CLASS(TYP_REL(k=16)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL16

END MODULE MOD_REL
PROGRAM MAIN

   USE MOD_REL
   IMPLICIT NONE

   INTEGER :: istat
   CHARACTER(len=80) :: msg
   TYPE (TYP_REL(k=8))  :: r8
   TYPE (TYP_REL(k=16)) :: r16

   ALLOCATE(r8%value(10,10), stat=istat, errmsg=msg, source=8.0_8)
   IF ( istat /= 0 ) STOP msg
   ALLOCATE(r16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
   IF ( istat /= 0 ) STOP msg
   CALL PRC1(r8)
   CALL PRC1(r16)
   PRINT *, shape(r8%value), shape(r16%value), r8%value(1,1), r16%value(1,1)

END PROGRAM MAIN

And here is another example with parameterized type-bound procedures, which gfortran as mentioned cannot compile, but ifort can!

MODULE MOD_REL

   TYPE :: TYP_REL(k)
      INTEGER, KIND :: k = 8
      REAL(KIND=k), ALLOCATABLE, DIMENSION(:, :) :: value
      CONTAINS
      PROCEDURE :: PRC1_REL8
      PROCEDURE :: PRC1_REL16
   END TYPE TYP_REL

CONTAINS

    SUBROUTINE PRC1_REL8(this)
        CLASS(TYP_REL(k=8)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL8


    SUBROUTINE PRC1_REL16(this)
        CLASS(TYP_REL(k=16)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL16

END MODULE MOD_REL
PROGRAM MAIN

   USE MOD_REL
   IMPLICIT NONE

   INTEGER :: istat
   CHARACTER(len=80) :: msg
   TYPE (TYP_REL(k=8))  :: r8
   TYPE (TYP_REL(k=16)) :: r16

   ALLOCATE(r8%value(10,10), stat=istat, errmsg=msg, source=8.0_8)
   IF ( istat /= 0 ) STOP msg
   ALLOCATE(r16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
   IF ( istat /= 0 ) STOP msg
   CALL r8%PRC1_REL8
   CALL r16%PRC1_REL16
   PRINT *, shape(r8%value), shape(r16%value), r8%value(1,1), r16%value(1,1)

END PROGRAM MAIN

If you want to get back to using GFortran after the bug has been fixed, you can enclose the ifort-specific parts of the code with #ifdef __INTEL_COMPILER

Conversely, for GFortran, it is #ifdef __GFORTRAN__

The downside of this approach is that now you need to preprocess the source file, but I think that shouldn’t be that much of a big deal. Renaming the file extension to capital letter .F90 will automatically invoke the preprocessor.

1 Like

Thanks @wyphan for your reply.

Conditional compilation (preprocessor) does not help in this situation as it does not reduce the definition of the derived types. Preprocessor increases the implementation in this situation, once for ifort (with PDT) and once for gfortran (without PDT).

Assuming that there is no parameterized derived type with type bound procedure (PDT), I am looking for an alternative way to avoid multiple definition of the derived type as they are different kinds.

In my experience, many of gfortran PDT bugs are in type-bound procedures and anything that involves len type parameter. Even if both features were bug-free I’d still avoid them. To me, the only relevant useful PDT feature appears to be the kind type parameter, which is the primary requirement for generic programming. So, if you keep the PDTs limited to types with only kind parameters and use generic interfaces (instead of type-bound procedures) that accept PDTs as arguments, you might be able to bypass the majority of the bugs (but definitely not all).
Ideally, the len type parameter should have also been designed as a compile-time constant, in my opinion. But the committee might have had good reasons to design it the way it is.

You are absolutely right. I have shown here the example of a type parameter without type-bound procedure.
But a derived type without type-bound procedures is only Fortran 90 and that is not what I want.
It seems that there is really no solution at the moment. Either I have to wait until the problems with gfortran are fixed (in fact the problems are not fixed since Fortran 2003 until today), or I have to do without gfortran.

As I have explained previously in an earlier thread with several practical examples, parameterized derived types (PDTs) are rather useful and there is indeed value in both the length type and kind type parameters.

  • From what I have heard, NAG Fortran has few issues, if any, with PDTs and they got PDTs right by the time they came around to offering it to their paying customers.
  • Intel Fortran (IFORT) has had its share of issues with PDTs over the years but thankfully Intel has devoted time and energy to get a lot right with PDTs in their latest version notwithstanding some pending bug reports.

With gfortran, should a community of new volunteers spring up and work together and consult with other experienced developers (see here under Contributing) such as Paul Thomas (@rouson might be able to help establish contact), considerable progress can be made.

I reckon the issues with PDTs are hardly unique when it comes to compiler bugs. Almost every compiler has struggled with getting hefty features implemented robustly starting with those introduced in the Fortran 2003 standard and the two subsequent revisions: intrinsic assignment with derived types and also allocation-upon-assignment, type inheritance, finalization, submodules, coarrays, enhanced interoperability with C, etc. to name only a few which have considerable problems with several compilers even now, enough for a distractor to construe the issues are troubling enough to lead astray an unwitting practitioner venturing into modern Fortran. I would rather the practitioners persevere with their computing pursuits with modern Fortran and egg and demand and work toward the implementations to get better along the way.

@Ali , if you are not following type-bound generic interfaces, then you may consider nonpolymorphic argument for the type e.g., TYPE(TYP_REL(k=8)) instead of CLASS(TYP_REL(k=8)).

Here is one way based on your code snippet: note there is generally a need for code duplication given where things are with the current standard. The hope with Fortran 202Y with enhanced Generics is this won’t be necessary.

Modified example
module kinds_m
   integer, parameter :: P8 = selected_real_kind( p=12 )
   integer, parameter :: P16 = selected_real_kind( p=2*precision(1.0_p8) )
end module 
module typ_rel
   use kinds_m, only : P8, P16
   type :: typ_r(k)
      integer, kind :: K = P8
      real(kind=k), allocatable, dimension(:, :) :: value
   contains
      procedure :: prc1 => prc_rel_8
      procedure :: prc2 => prc_rel_16
      generic :: prc => prc1, prc2
   end type typ_r
contains
   subroutine prc_rel_8(this)
      class(typ_r(K=P8)) :: this
      print *, this%k
   end subroutine
   subroutine prc_rel_16(this)
      class(typ_r(K=P16)) :: this
      print *, this%k
   end subroutine
end module typ_rel

program main
   use kinds_m, only : P8, P16
   use typ_rel, only : typ_r
   integer :: istat
   character(len=80) :: msg
   type (typ_r) :: r8
   type (typ_r(P16)) :: r16

   allocate(r8%value(10,10), stat=istat, errmsg=msg, source=8.0_8)
   if ( istat /= 0 ) stop msg
   allocate(r16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
   if ( istat /= 0 ) stop msg
   call r8%prc()
   call r16%prc()
   print *, shape(r8%value), shape(r16%value), r8%value(1,1), r16%value(1,1)
end program main

C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.30.30706.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
8
16
10 10 5 5 8.00000000000000 16.0000000000000000000000000000000

1 Like

@kargl It would be great, but I have no experience with any compiler, so I think for me life is shorter than understanding the compiler and fixing this bug. :wink:

@FortranFan thanks for your reply.

If in this example the TYP_REL is extended to TYP_REL2, then data polymorphism and procedure polymorphism is still possible.
Did I misunderstand something?

MODULE MOD_REL

    TYPE :: TYP_REL(k)
        INTEGER, KIND :: k = 8
        REAL(KIND=k), ALLOCATABLE, DIMENSION(:, :) :: value
    END TYPE TYP_REL

    TYPE, EXTENDS(TYP_REL) :: TYP_REL2(k2)
        INTEGER, KIND :: k2 = 8
        REAL(KIND=k2), ALLOCATABLE, DIMENSION(:, :) :: value2
    END TYPE TYP_REL2

 
    INTERFACE PRC1
        MODULE PROCEDURE PRC1_REL8
        MODULE PROCEDURE PRC1_REL16
    END INTERFACE PRC1
 
 CONTAINS
 
    SUBROUTINE PRC1_REL8(this)
        CLASS(TYP_REL(k=8)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL8


    SUBROUTINE PRC1_REL16(this)
        CLASS(TYP_REL(k=16)) :: this
        PRINT *, this%k
    END SUBROUTINE PRC1_REL16
 
 END MODULE MOD_REL
    USE MOD_REL
    IMPLICIT NONE
 
    INTEGER :: istat
    CHARACTER(len=80) :: msg
    TYPE (TYP_REL(k=8))    :: r8
    TYPE (TYP_REL(k=16))   :: r16
    TYPE (TYP_REL2(k=16))  :: rr16
    TYPE (TYP_REL2(k2=16)) :: rrr16
 
    ALLOCATE(r8%value(10,10), stat=istat, errmsg=msg, source=8.0_8)
    IF ( istat /= 0 ) STOP msg
    ALLOCATE(r16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
    IF ( istat /= 0 ) STOP msg
    ALLOCATE(rr16%value(5,5), stat=istat, errmsg=msg, source=16.0_16)
    IF ( istat /= 0 ) STOP msg
    ALLOCATE(rrr16%value2(5,5), stat=istat, errmsg=msg, source=16.0_16)
    IF ( istat /= 0 ) STOP msg
    CALL PRC1(r8)
    CALL PRC1(r16)
    CALL PRC1(rr16)
    CALL PRC1(rrr16)
    PRINT *, shape(r8%value), shape(r16%value), r8%value(1,1), r16%value(1,1), rr16%value(1,1), rrr16%value2(1,1)
 
 END PROGRAM MAIN

           8
          16
          16
           8
          10          10           5           5   8.00000000000000     
   16.0000000000000000000000000000000      
   16.0000000000000000000000000000000      
   16.0000000000000000000000000000000 

@FortranFan Do you have any suggestion on how this example could be done without code duplication using gfortran, considering the current issues with PDTs? This is actually what I am looking for.

@Ali , my understanding is you’ve limited and not very good choices:

  • using either the standard-based INCLUDE statement option and/or
  • some (intelligent) preprocessor and its macro capabilities (e.g., FYPP),

you can get to a point of minimizing code duplication but not avoiding duplication completely, all the while incurring other “costs” with developing your solution (due to complexities and other dependencies).

Unfortunately that is where things are currently with the Fortran (gfortran) ecosystem and its language standard.

2 Likes

Yes, it’s possible but with significant departure from KISS principle. And some penalty due to polymorphic dummy arguments assuming performance is important which is usually the case with wanting to use Fortran.

@FortranFan, thanks for your suggestions. You are absolutely right.

There is no way to write generic derived types without PDTs in gfortran, not even with preprocessor or fypp, or … Without PDTs, any derived type name will have to explicitly depend on the kinds of the components types. Once you write types with explicit kind names suffixed to it, it is not generic anymore (in fact, this is what gfortran does internally to create PDTs). PDTs are the only way forward.
I have revived an old thread on PDTs in gfortran whose development is led by Paul Thomas, in the hope of getting an update on the status and future of PDTs implementation in gfortran and catalyzing the bug fixes. Join the discussion there if you need PDTs in gfortran.
On the positive side, several commercial compilers already have full working implementations of PDTs.

1 Like