Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.
28446 Discussions

Using Generic Interfaces and Parameterized Types for selective early binding

Cristian_P_
Beginner
643 Views

I am using a parameterized type (called dispersion_type in the code) to select a function based on the value of a kind parameter of the type (namely, fkind). The different functions would have identical signatures if not for the additional argument of type dispersion_type(fkind).  With the additional argument, the functions can be collected under a  generic interface.  If the name of the generic interface is different from dispersion_type, the program works as desired.

If the name is the same, the code compiles and works with IFORT 15.0.1, but fails with IFORT 16.0.0, with the error

early_binding.f90(44): error #6593: The number of expressions in a structure constructor differs from the number of components of the derived type.   [DISPERSION_FORCE#2]

I think the code is correct though: in line 44, the second argument of dispersion_type(5., *) should call the structure constructor of dispersion_type, since there is no match available under the generic name.  The call to dispersion_type(5., *) itself should be to one of the overloaded versions available under the generic name.  It seems IFORT 16.0.0 decides there is no match and then tries to invoke the structure constructor again, which results in an error. Comments?

Module pairwise_potential
! Using a generic interface to bind procedures to parameterized types at compile times. 
! The method works if the name of the type dispersion_force is DIFFERENT
! from the name of the generic interface, but it should work when the names
! are the same, too. That would be neater. 
   Implicit None

   Type dispersion_force(fkind)
      Integer, Kind :: fkind = 2
   End Type dispersion_force

   Interface dispersion_force
      Module Procedure first_force
      Module Procedure second_force
      Module Procedure third_force
   End Interface dispersion_force

Contains

   Real Function first_force(rs, fkind)
      Real, Intent(In)                  :: rs
      Type(dispersion_force(1)), Intent(In) :: fkind

      first_force = 1.
   End Function first_force

   Real Function second_force(rs, fkind)
      Real, Intent(In)                  :: rs
      Type(dispersion_force(2)), Intent(In) :: fkind

      second_force = 2.
   End Function second_force

   Real Function third_force(rs, fkind)
      Real, Intent(In)                  :: rs
      Type(dispersion_force(3)), Intent(In) :: fkind

      third_force = 3.
   End Function third_force

   Subroutine verify_association
      Integer, Parameter :: fkind = 2

      Print *, 'The force kind is ', dispersion_force(5., dispersion_force(fkind)())

      !The above works with IFORT 15.0.1, but does not compile with IFORT 16.0.0
      !Furthermore, since the type dispersion_force has the default fkind=2, I expect
      !the following to also compile

      !Print*, 'The force kind is ', dispersion_force(5., dispersion_force)
      !Print*, 'The force kind is ', dispersion_force(5., dispersion_force(fkind))
   End Subroutine verify_association

End Module pairwise_potential

Program test
   Use pairwise_potential

   Call verify_association
End Program test

 

0 Kudos
1 Solution
FortranFan
Honored Contributor II
643 Views

Looks like a bug in Intel Fortran with parameterized derived type (PDT) toward the facility starting with Fortran 2003 for a generic name in an interface being the same as derived type name.  The facility works with a derived type as shown below, but not with PDT.

module m

   implicit none

   private

   type, public :: dt
      integer :: k = 1
   end type dt

   interface dt
      module procedure k_dt
   end interface

   public :: verify

contains

   function k_dt( rin, t ) result(rout)

      real, intent(in)     :: rin
      type(dt), intent(in) :: t
      !.. function result
      real :: rout

      rout = rin + real( t%k, kind=kind(rout) )

   end function k_dt

   subroutine verify()

      print *, " In verify: ", dt( rin=1.0, t=dt(k=1) )

      return

   end subroutine verify

end module m
Compiling with Intel(R) Visual Fortran Compiler 16.0.1.146 [Intel(R) 64]...
m.f90

m - 0 error(s), 0 warning(s)

Notice the same error as in the original post for the case with PDT:

module m

   implicit none

   private

   type, public :: pdt(k)
      integer, kind :: k = 1
   end type pdt

   interface pdt
      module procedure k_pdt
   end interface

   public :: verify

contains

   function k_pdt( rin, t ) result(rout)

      real, intent(in)           :: rin
      type(pdt(k=1)), intent(in) :: t
      !.. function result
      real :: rout

      rout = rin + real( t%k, kind=kind(rout) )

   end function k_pdt

   subroutine verify()

      print *, " In verify: ", pdt( rin=1.0, t=pdt(k=1)() )

      return

   end subroutine verify

end module m
Compiling with Intel(R) Visual Fortran Compiler 16.0.1.146 [Intel(R) 64]...
m.f90
m.f90(32): error #6593: The number of expressions in a structure constructor differs from
the number of components of the derived type.   [PDT#1]
compilation aborted for m.f90 (code 1)

m - 2 error(s), 0 warning(s)

 

View solution in original post

0 Kudos
6 Replies
Steven_L_Intel1
Employee
643 Views

Thanks, we'll take a look.

0 Kudos
FortranFan
Honored Contributor II
644 Views

Looks like a bug in Intel Fortran with parameterized derived type (PDT) toward the facility starting with Fortran 2003 for a generic name in an interface being the same as derived type name.  The facility works with a derived type as shown below, but not with PDT.

module m

   implicit none

   private

   type, public :: dt
      integer :: k = 1
   end type dt

   interface dt
      module procedure k_dt
   end interface

   public :: verify

contains

   function k_dt( rin, t ) result(rout)

      real, intent(in)     :: rin
      type(dt), intent(in) :: t
      !.. function result
      real :: rout

      rout = rin + real( t%k, kind=kind(rout) )

   end function k_dt

   subroutine verify()

      print *, " In verify: ", dt( rin=1.0, t=dt(k=1) )

      return

   end subroutine verify

end module m
Compiling with Intel(R) Visual Fortran Compiler 16.0.1.146 [Intel(R) 64]...
m.f90

m - 0 error(s), 0 warning(s)

Notice the same error as in the original post for the case with PDT:

module m

   implicit none

   private

   type, public :: pdt(k)
      integer, kind :: k = 1
   end type pdt

   interface pdt
      module procedure k_pdt
   end interface

   public :: verify

contains

   function k_pdt( rin, t ) result(rout)

      real, intent(in)           :: rin
      type(pdt(k=1)), intent(in) :: t
      !.. function result
      real :: rout

      rout = rin + real( t%k, kind=kind(rout) )

   end function k_pdt

   subroutine verify()

      print *, " In verify: ", pdt( rin=1.0, t=pdt(k=1)() )

      return

   end subroutine verify

end module m
Compiling with Intel(R) Visual Fortran Compiler 16.0.1.146 [Intel(R) 64]...
m.f90
m.f90(32): error #6593: The number of expressions in a structure constructor differs from
the number of components of the derived type.   [PDT#1]
compilation aborted for m.f90 (code 1)

m - 2 error(s), 0 warning(s)

 

0 Kudos
Cristian_P_
Beginner
643 Views

Thanks for the concise example, FortranFan.  I think your example settles it as a bug. 

PDTs seem an important feature of Fortran.  Maybe Fortran will also adopt named enumerations (most of the syntax is there anyway, having been introduced for C interoperability).  I could use an easy way of creating a restricted set of integer parameters (restricted to "valid type parameters").  

0 Kudos
Steven_L_Intel1
Employee
643 Views

Thanks from me as well.  Escalated as issue DPD200380357.

0 Kudos
Steven_L_Intel1
Employee
643 Views

Fixed for a major release later this year.

0 Kudos
Cristian_P_
Beginner
643 Views

Thanks, Steve.

0 Kudos
Reply