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

Using parameterized derived types

Simon_Geard
New Contributor I
1,046 Views

I've been looking at this new feature and would like to understand more. The code below doesn't compile so my immediate question is should it or is there another way to achieve what I'm trying to do. Another question relates to extending a parameterized derived type: is it possible? what is the syntax? My final question is can such types be specialized (which C++ supports with templates)?

Thanks.

module vectors

    use iso_fortran_env
    implicit none
    
    public :: Vector, operator(.cross.)
    
    type :: Vector(n, k)
        private
        integer, len  :: n
        integer, kind :: k = real64
        real(k)       :: v(n)
    contains
        generic, public    :: assignment(=) => set_a_vectors, set_vectors
        generic, public    :: operator(==) => cf_vectors
        generic, public    :: operator(/=) => cfx_vectors
        procedure, private :: set_a_vectors
        procedure, private :: set_vectors
        procedure, private :: cf_vectors
        procedure, private :: cfx_vectors
    end type Vector
    
    interface operator(.cross.)
        module procedure cross_v3_vectors
        module procedure cross_v2_vectors
    end interface
    
    ! Trying to create a specialization of Vector(n) but this doesn't compile.
    !type, extends(Vector(2)) :: VC2_t
    !end type VC2_t
    
    private
    
contains
    elemental subroutine set_vectors(v, a)
        class(Vector(*)), intent(out) :: v
        class(Vector(*)), intent(in)  :: a
        v%v = a%v
    end subroutine set_vectors
    
    pure subroutine set_a_vectors(v, a)
        class(Vector(*)), intent(out) :: v
        real(8), intent(in) :: a(:)
        v%v = a
    end subroutine set_a_vectors
    
    elemental logical function cf_vectors(v1, v2)
        class(Vector(*)), intent(in) :: v1, v2
        cf_vectors = (v1%n == v2%n)
        if (cf_vectors) then
            cf_vectors = all(v1%v == v2%v)
        end if
    end function cf_vectors
    
    elemental logical function cfx_vectors(v1, v2)
        class(Vector(*)), intent(in) :: v1, v2
        cfx_vectors = .not. (v1 == v2)
    end function cfx_vectors

    function cross_v3_vectors(v1, v2) result(r)
        type(Vector(3)) :: r
        type(Vector(3)), intent(in) :: v1, v2
    end function cross_v3_vectors

    function cross_v2_vectors(v1, v2) result(r)
        type(Vector(2)) :: r
        type(Vector(2)), intent(in) :: v1, v2
    end function cross_v2_vectors


end module vectors


program main
    use vectors
    imlicit none

    type(Vector(2)) :: s2, t2, u2, v2
    type(Vector(3)) :: u3, v3
    
    ! Assignment from array
    s2 = [1.0d0, 2.0d0]
    t2 = [-3.0d0, 2.0d0]
    
    ! Cross product
    u2 = (s2 .cross. t2)
        
end program main

 

0 Kudos
10 Replies
Simon_Geard
New Contributor I
1,046 Views

Just to follow up:

1) line 76 should say 'implicit none'

2) When I compile this code I get


ifort vectors.f90

Intel(R) Visual Fortran Intel(R) 64 Compiler for applications running on Intel(R) 64, Version 16.0.3.207 Build 20160415
Copyright (C) 1985-2016 Intel Corporation.  All rights reserved.

vectors.f90(86): error #8745: All nondeferred nonassumed type parameters of the dummy argument must have the same values as the corresponding type parameters of the actual argument
.   [S2]
    u2 = (s2 .cross. t2)
----------^
vectors.f90(86): error #8745: All nondeferred nonassumed type parameters of the dummy argument must have the same values as the corresponding type parameters of the actual argument
.   [T2]
    u2 = (s2 .cross. t2)
---------------------^
compilation aborted for vectors.f90 (code 1)

 

0 Kudos
IanH
Honored Contributor II
1,046 Views

My experience is that some aspects of compiler support for parametrised derived types is a bit flaky - I suspect the nature of the error message that you are seeing reflects that.

There are two functions in the .cross. generic interface.  Any pair of specific procedures in a generic interface must be distinguishable, if the procedures have the same number of non-optional arguments then at least one of the non-optional arguments must be distinguishable.  Arguments are distinguished on the basis of their type, kind and rank.  Both of the functions in the .cross. generic interface have two non-optional scalar arguments that are of type Vector, with a kind parameter k with the value of the real64 named constant - those arguments are not distinguishable.  This is an error in the program that the compiler should complain about when it compiles the module.

You cannot specialise a parametrised type in the manner you suggest.  An extension of a type is an extension of a type - not a extension of type+parameters, the extension inherits the type parameters of its parent type - they are then available for specification in type specifications as if they were declared in the extended type.  If that is not appropriate for your use case, then consider using aggregation rather than inheritance.

What you can do as a form of specialisation is have different procedures called for different values of a kind parameter of your type.  In your example code, the n type parameter is a length parameter - so it is not used for generic resolution.  Subject to other requirements of your code, you could make this a kind parameter.

The downside with this approach is that you actually have to specialise every specific procedure that takes an argument of type Vector - there is no support in the language for "generic programming" that lets you automatically instantiate a specific procedure for a particular kind value on demand.  I personally find this a very serious short coming with the use of kind parametrisation., reducing its utility to barely more than a minor namespace convenience.

As a loose concept - kind parameters are for compile time parametrisation only, length parameters permit runtime parametrisation.

Perhaps you could elaborate on what it is that you are trying to do.

(You probably do not need the defined assignment for assignment of vector to vector - that is just supplanting intrinsic assignment.)

0 Kudos
Andrew_Smith
New Contributor III
1,046 Views

Your example should compile OK since you pass corresponding types with same length parameters. You could have implemented cross with one function:

function cross_vectors(v1, v2) result(r)
	type(Vector(*)), intent(in) :: v1, v2
        type(Vector(v1%n)) :: r
        ...
end

But the compiler is likely give you an ICE at some point. I would not have used the understatement of "some aspects of compiler support for parametrised derived types is a bit flaky", it's far worse. My support request has been open since February last year.

I think the reason for this feature not being properly supported is because Intel see it as just a programming nicity to aid generic programming.

But it will leed to improved performance too which is something I believe has higher priority for Intel.

1. The space for the parametrized variable size vector is allocated from the stack for local variables and function returns. We no longer need to allocate the vector from the heap. This improves performance for parallel code in particular.

2. The declaration of the length is more visible to the compiler and also, vector maths using the types can assume the lengths match. So for instance in cross_vectors v1%v and v2%v will be assumed to have same size even though we did not says so (That is according to Intel support). Both these things improve oportunity for the compiler to apply hardware vectorization.

0 Kudos
IanH
Honored Contributor II
1,046 Views

Andrew Smith wrote:
2. The declaration of the length is more visible to the compiler and also, vector maths using the types can assume the lengths match. So for instance in cross_vectors v1%v and v2%v will be assumed to have same size even though we did not says so (That is according to Intel support). Both these things improve oportunity for the compiler to apply hardware vectorization.

That doesn't sound right.  The declaration `type(Vector(*)), intent(in) :: v1, v2` does not imply or require (in isolation) that the length parameter of v1 and v2 are or must be the same.  Both dummy arguments independently assume the value of the length parameter from the associated actual argument.  An analogy can be made with the length parameter for character arguments - for dummy arguments declared `character(*) :: s1, s2`, your actual arguments could be a short string "x" and "a much longer string".

Things would be different for a pair of dummy argument declarations such as `type(Vector(*)) :: v1 ; type(Vector(v1%n)) :: v2` - akin to what has been used to describe the function result.

 

0 Kudos
Simon_Geard
New Contributor I
1,046 Views

Really I'm just trying to understand this new feature in the context of a particular example (I think better that way).

If I understand you correctly then although I might declare a variable to be type(Vector(2)) the actual type is Vector which is why cross_v3_vectors and cross_v2_vectors can't be distunguished.

I suppose I was hoping I could use this feature to provide some support for generic programming instead of my current scheme of using the c-preprocessor but from what you say that isn't possible.

0 Kudos
Steven_L_Intel1
Employee
1,046 Views

First, I have to object to Andrew's characterization about our support of language features. If it's a feature of the standard that we have implemented, our intention is to support it completely, no matter what some might think of the feature's value. In the particular case of PDT length parameters, this is a VERY difficult feature to implement and we were one of the first to do so. That bugs exist in various corners is to be expected - and also to be expected is that if we learn about bugs we'll fix them. We don't have the liberty of considering particular language features "second class".

Now - the problem here relates to the generic selection. The compiler is evidently not properly resolving the generic and matching cross_v3_vectors when it should keep looking. If cross_v3_vectors is removed from the generic, it works. Similarly, if Vector(*) is used in the manner Andrew describes, it works.

I have escalated this as issue DPD200413335.

0 Kudos
IanH
Honored Contributor II
1,046 Views

Steve Lionel (Intel) wrote:
Now - the problem here relates to the generic selection. The compiler is evidently not properly resolving the generic and matching cross_v3_vectors when it should keep looking. If cross_v3_vectors is removed from the generic, it works. Similarly, if Vector(*) is used in the manner Andrew describes, it works.

I still think the generic interface for .cross. violates F2008 C1212.  Length type parameters should not influence generic resolution at all.

0 Kudos
Steven_L_Intel1
Employee
1,046 Views

This is one of those things that has one chasing across the standard trying to nail down the words.

  • C1212 requires that the arguments be "distinguishable".
  • "distinguishable" (12.4.3.4.5p3) references "TKR compatible".
  • "TKR compatible" references "type compatible" and mentions kind parameters

So you're right that length parameters don't count here and the compiler should have disallowed the generic.

0 Kudos
IanH
Honored Contributor II
1,046 Views

Simon Geard wrote:

Really I'm just trying to understand this new feature in the context of a particular example (I think better that way).

If I understand you correctly then although I might declare a variable to be type(Vector(2)) the actual type is Vector which is why cross_v3_vectors and cross_v2_vectors can't be distunguished.

I suppose I was hoping I could use this feature to provide some support for generic programming instead of my current scheme of using the c-preprocessor but from what you say that isn't possible.

I'll guess a bit at the sort of example you might be seeking, and present two options - one using length type parameters, the other kind type parameters.

The length type parameter case uses assumed type parameters to make a specific procedure applicable to multiple values of the n parameter.  (All the specific procedures sit behind a generic identifier, but there is only one specific procedure per identifier - so using the generics is just a syntax nicety that lets us use defined assignment and in-line operators.) Where behaviour depends on a particular value of the n parameter, a runtime decision is used within the specific procedure - you would ordinarily expect some sort of runtime cost for that decision, how substantial will depend on circumstances.  As discussed above, some procedures have a requirement that the length type parameter of their arguments meet certain criteria (be the same in this case) - the compiler may warn us if we botch that or have some other sort of blatantly obvious mismatch in parameters.  However, because length type parameters can be deferred (decided at runtime), it will not always be obvious to the compiler that there is a problem.

module vectors
  use iso_fortran_env, only: real64
  implicit none
  
  private
  
  public :: Vector
  
  type :: Vector(n, k)
!    private
    integer, len  :: n
    integer, kind :: k = real64
    real(k)       :: v(n)
  contains
    generic, public :: assignment(=) => set_a_vectors
    generic, public :: operator(==) => cf_vectors
    generic, public :: operator(/=) => cfx_vectors
    generic, public :: operator(.cross.) => cross_vector
    procedure, private :: set_a_vectors
    procedure, private :: cf_vectors
    procedure, private :: cfx_vectors
    procedure, private :: cross_vector
  end type Vector
contains
  pure subroutine set_a_vectors(v, a)
    class(Vector(*)), intent(out) :: v
    real(real64), intent(in) :: a(:)
    v%v = a
  end subroutine set_a_vectors
  
  elemental logical function cf_vectors(v1, v2)
    class(Vector(*)), intent(in) :: v1
    class(Vector(v1%n)), intent(in) :: v2
    
    cf_vectors = all(v1%v == v2%v)
  end function cf_vectors
  
  elemental logical function cfx_vectors(v1, v2)
    class(Vector(*)), intent(in) :: v1
    class(Vector(v1%n)), intent(in) :: v2
    
    cfx_vectors = .not. (v1 == v2)
  end function cfx_vectors
  
  function cross_vector(v1, v2) result(r)
    class(Vector(*)), intent(in) :: v1
    class(Vector(v1%n)), intent(in) :: v2
    type(Vector(3)) :: r
    
    if (v1%n == 2) then
      r%v = [  &
          0.0_real64,  &
          0.0_real64,  &
          v1%v(1) * v2%v(2) - v1%v(2) * v2%v(1) ]
    else if (v1%n == 3) then
      r%v = [  &
          v1%v(2) * v2%v(3) - v1%v(3) * v2%v(2),  &
          v1%v(3) * v2%v(1) - v1%v(1) * v2%v(3),  &
          v1%v(1) * v2%v(2) - v1%v(2) * v2%v(1) ]
    else
      error stop 'wot??'
    end if
  end function cross_vector
end module vectors


program pdt_using_len
  use vectors
  implicit none
  
  type(Vector(2)) :: a, b
  ! Make it allocatable with a deferred parameter, just for fun.
  type(Vector(:)), allocatable :: c
  
  ! If we botched the declaration, the compiler may complain later.
!  type(Vector(2)) :: c
  
  ! Assignment from array
  a = [1.0d0, 2.0d0]
  ! Structure constructor.
  b = Vector(2)([-3.0d0, 2.0d0])
  
  ! Cross product
  c = a .cross. b
  
  print *, c%n
  print *, c%v
  
  ! Incorrect call - may get a compiler error.
!  b = c .cross. a
end program pdt_using_len

If n is made a kind type parameter, then effectively specific procedures need to be provided for each supported case.  We hide those specific procedures behind a generic identifier as a naming convenience - the relevant specific gets selected on the basis of the kind parameter of the actual arguments.  The compile selection of specific procedure avoids the runtime decision based on the value of `n` in the implementation of the cross product.

Without using the preprocessor or INCLUDE tricks, this tends to require a lot more code than the length type parameter example.  The bodies of each specific procedure start looking very similar though, so there is potential for some sort of token substitution technique to cut down on the amount of "original" code.  (The amount of unique code per value of n could be even less than what I have in the following example, but the compiler appears to be having some issues with the use of kind type parameter inquiries in constant expressions.)

With the use of kind parameters, mismatches in parameter for a particular procedure call are very likely to be detected by the compiler, as kind parameter values are always known at runtime and the compiler effectively has to check that parameters match between actual and dummy arguments in order to work out which procedure to call.  Botch the kind parameters - no specific procedure will match - compiler won't know what to call so it will have a whinge.

module vectors
  use iso_fortran_env, only: real64
  implicit none
  
  private
  
  public :: Vector
  
  type :: Vector(n, k)
!    private
    integer, kind  :: n
    integer, kind :: k = real64
    real(k)       :: v(n)
  contains
    generic, public :: assignment(=) => set_a_vector2, set_a_vector3
    generic, public :: operator(==) => cf_vector2, cf_vector3
    generic, public :: operator(/=) => cfx_vector2, cfx_vector3
    generic, public :: operator(.cross.) => cross_vector2, cross_vector3
    procedure, private :: set_a_vector2
    procedure, private :: cf_vector2
    procedure, private :: cfx_vector2
    procedure, private :: cross_vector2
    procedure, private :: set_a_vector3
    procedure, private :: cf_vector3
    procedure, private :: cfx_vector3
    procedure, private :: cross_vector3
  end type Vector
contains
  pure subroutine set_a_vector2(v, a)
    class(Vector(2)), intent(out) :: v
    real(real64), intent(in) :: a(:)   ! could be declared (v%n)
    
    v%v = a
  end subroutine set_a_vector2
  
  elemental function cf_vector2(v1, v2) result(r)
    class(Vector(2)), intent(in) :: v1
    class(Vector(2)), intent(in) :: v2
    logical :: r
    
    r = all(v1%v == v2%v)
  end function cf_vector2
  
  elemental function cfx_vector2(v1, v2) result(r)
    class(Vector(2)), intent(in) :: v1
    class(Vector(2)), intent(in) :: v2
    logical :: r
    
    r = .not. (v1 == v2)
  end function cfx_vector2
  
  function cross_vector2(v1, v2) result(r)
    class(Vector(2)), intent(in) :: v1
    class(Vector(2)), intent(in) :: v2
    type(Vector(3)) :: r
    
    r%v = [  &
        0.0_real64,  &
        0.0_real64,  &
        v1%v(1) * v2%v(2) - v1%v(2) * v2%v(1) ]
  end function cross_vector2
  
  
  pure subroutine set_a_vector3(v, a)
    class(Vector(3)), intent(out) :: v
    real(real64), intent(in) :: a(:)
    
    v%v = a
  end subroutine set_a_vector3
  
  elemental function cf_vector3(v1, v2) result(r)
    class(Vector(3)), intent(in) :: v1
    class(Vector(3)), intent(in) :: v2
    logical :: r
    
    r = all(v1%v == v2%v)
  end function cf_vector3
  
  elemental function cfx_vector3(v1, v2) result(r)
    class(Vector(3)), intent(in) :: v1
    class(Vector(3)), intent(in) :: v2
    logical :: r
    
    r = .not. (v1 == v2)
  end function cfx_vector3
  
  function cross_vector3(v1, v2) result(r)
    class(Vector(3)), intent(in) :: v1
    class(Vector(3)), intent(in) :: v2
    type(Vector(3)) :: r
    
    r%v = [  &
        v1%v(2) * v2%v(3) - v1%v(3) * v2%v(2),  &
        v1%v(3) * v2%v(1) - v1%v(1) * v2%v(3),  &
        v1%v(1) * v2%v(2) - v1%v(2) * v2%v(1) ]
  end function cross_vector3
end module vectors


program main
  use vectors
  implicit none
  
  type(Vector(2)) :: a, b
  type(Vector(3)) :: c
  
  ! Assignment from array
  a = [1.0d0, 2.0d0]
  ! Structure constructor.
  b = Vector(2)([-3.0d0, 2.0d0])
  
  ! Cross product
  c = a .cross. b
  
  print *, c%n
  print *, c%v
  
  ! Incorrect call - highly likely to get a compiler error.
!  b = c .cross. a
end program main

I used the current beta compiler to test all of the above.

0 Kudos
Simon_Geard
New Contributor I
1,046 Views

Thank you for this comprehensive information, I am studying it.

0 Kudos
Reply