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

parameterised derived type default kind parameters

Nicholas_B_
Beginner
3,817 Views

Parameterised derived types with kind parameters which have default values set to parameters are not working as I expect in Intel Visual Fortran Compiler XE 15.0.2.179. Is this a bug or are my expectations wrong?

The following code shows the issue:

module imp_module

  implicit none
  private

  integer, parameter :: n = 5

  type, public :: dt(k)
     integer, kind :: k = n
     integer, dimension(k) :: x
  end type dt

end module imp_module

program imp_prog

  use imp_module

  type(dt) :: x

  print *,x

end program imp_prog

Compiling the code gives:

Deleting intermediate files and output files for project 'imp', configuration 'Debug|Win32'.
Compiling with Intel(R) Visual Fortran Compiler XE 15.0.2.179 [IA-32]...
ifort /nologo /debug:full /Od /warn:interfaces /module:"Debug\\" /object:"Debug\\" /Fd"Debug\vc120.pdb" /traceback /check:bounds /check:stack /libs:dll /threads /dbglibs /c /Qvc12 /Qlocation,link,"C:\Program Files (x86)\Microsoft Visual Studio 12.0\VC\\bin" "C:\Users\Nicholas\Documents\imp_bug\imp_module.f90"
ifort /nologo /debug:full /Od /warn:interfaces /module:"Debug\\" /object:"Debug\\" /Fd"Debug\vc120.pdb" /traceback /check:bounds /check:stack /libs:dll /threads /dbglibs /c /Qvc12 /Qlocation,link,"C:\Program Files (x86)\Microsoft Visual Studio 12.0\VC\\bin" "C:\Users\Nicholas\Documents\imp_bug\imp_prog.f90"
C:\Users\Nicholas\Documents\imp_bug\imp_prog.f90(5): error #6683: A kind type parameter must be a compile-time constant.   
  type(dt) :: x
^
compilation aborted for C:\Users\Nicholas\Documents\imp_bug\imp_prog.f90 (code 1)


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

 

0 Kudos
23 Replies
FortranFan
Honored Contributor III
3,250 Views

In your type declaration for dt, did you intend to use the kind parameter k as a length parameter for x too?  I'm not sure if that is standard-conforming.  Nonetheless, one should be able to declare a type, such as x in your main program, with default type parameters when default values are provided, as you do with kind parameter k.  I think that's a bug in Intel Fortran that it complains about the declaration in the main program.  Now there might already be a tracking incident open with Intel Fortran on this issue.  Currently the following works with Intel Fortran:

module imp_module
  
  implicit none
  
  private

  integer, parameter :: n = 5
  
  type, public :: dt(k,m)
     integer, kind :: k = n
     integer, len :: m = 1
     integer(kind=k), dimension(m) :: x
  end type dt

end module imp_module
program imp_prog

  use, intrinsic :: iso_fortran_env, only : i4 => int32
  
  use imp_module, only : dt

  type(dt(k=i4,m=5)) :: x !.. type(dt) :: x should work too, I think

  print *, "x%k = ", x%k, ", x%m = ", x%m

end program imp_prog

Upon, execution:

 x%k =  4 , x%m =  5
Press any key to continue . . .

 

0 Kudos
Nicholas_B_
Beginner
3,250 Views

Thank you for your comments.

I did intend to use the kind parameter as the dimesnion of the array component because I want it to be fixed at compile time so that the compiler can optimise it.

I don't have a copy of the Fortran 2003 stnadard but the J3/14-007r2 (F2015 Working Document) says:

4.5.3 Derived-type parameter

...

5 A type parameter may be used as a primary in a specification expression (7.1.11) in the derived-type-def . A kind
   type parameter may also be used as a primary in a constant expression (7.1.12) in the derived-type-def .

Note 4,24 also includes:

TYPE :: t1(k1,k2)
   INTEGER,KIND :: k1,k2
   REAL(k1) a(k2)
END TYPE

 

0 Kudos
IanH
Honored Contributor III
3,250 Views

FortranFan wrote:

In your type declaration for dt, did you intend to use the kind parameter k as a length parameter for x too?  I'm not sure if that is standard-conforming.

You can (subject to your compile playing by the rules) use both kind and length type parameters in specification expressions (which is what the expression for the extent of a dimension of a component is) inside the type body.  There's no requirement that kind type parameters only be used for specifying the kind parameters of components. 

(What you can't do is use the value of length type parameters in constant expressions inside the type body.)

Because they can be used in constant expressions, kind parameter values in type specifiers (in the absence of a default expression) need to be specified by constant expressions, which reduces the flexibility in how they are specified relative to length type parameters.  So there is a trade-off between broader applicability in where they can be referenced, against a loss of flexibility in how they can be specified.

A crude analogy could be made with ordinary named constants and variables - you can [perhaps too obviously] use named constants in things other than constant expressions (but you can't use the value of variables in constant expressions).  Whether something "should" be a constant is probably practically innate to you - the same basic principles apply to whether to make a type parameter a kind or length parameter.

That said, given kind parameters are used in procedure resolution and the capability of the language today, beyond the aspect of putting the specification of a constant in the same namespace as the type that uses it, I typically find kind parameters of marginal value.  But length type parameters are just awesome.

0 Kudos
Nicholas_B_
Beginner
3,250 Views

The last comment about kind parameters being used in procedure resolution is the key point in my wanting to use kind type parameters as component dimensions. Using kind parameters means that I only have to code the type once. Current Fortran limitations means I have to code the procedures which use the type several times but I could use include statements to minimise duplictaion.

0 Kudos
Nicholas_B_
Beginner
3,250 Views

Here is an example of using parameter kind types, include files and generic interfcaes to simulate generic programming:

program pdt_prog

  use pdt_all_module

  implicit none

  type(dt(2)) :: x2
  type(dt(3)) :: x3
  
  call print(x2)
  call print(x3)
  
end program pdt_prog
module pdt_all_module

  use pdt2_module
  use pdt3_module

end module pdt_all_module
module pdt2_module

  include 'pdt_preincl.f90'

  integer, parameter :: n = 2

  include 'pdt_incl.f90'

end module pdt2_module
module pdt3_module

  include 'pdt_preincl.f90'

  integer, parameter :: n = 3

  include 'pdt_incl.f90'
  
end module pdt3_module
pdt_preincl.f90:
  use pdt_module

  implicit none
  private

pdt_incl.f90:
  public :: print, dt
  
  interface print
    module procedure :: print_p
  end interface
  
  contains
  
  subroutine print_p(a)
    type(dt(n)), intent(in) :: a
    print *,a
  end subroutine print_p
module pdt_module

  implicit none
  private

  type, public :: dt(k)
     integer, kind :: k
     integer, dimension(k) :: x = 0
  end type

end module pdt_module

 

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

Nicholas B. wrote:

Here is an example of using parameter kind types, include files and generic interfcaes to simulate generic programming: ..

 

It's totally unclear what point you're trying to make: either your example fails to reflect it or you're making it more complicated:

module m

   use, intrinsic :: iso_fortran_env, only : i4 => int32

   implicit none

   private

   public :: i4

   type, public :: dt(n)
      private
      integer, len :: n = 1
      integer(kind=i4), public :: x(n)
   contains
      procedure, pass(this), public :: print => print_dt_x
   end type dt

contains

   subroutine print_dt_x(this)

      class(dt(*)), intent(in) :: this

      print *, " this%x = ", this%x

      return

   end subroutine print_dt_x

end module m
program p

   use m, only : dt

   type(dt(n=2)) :: x2
   type(dt(n=3)) :: x3

   x2%x = [ 1, 2 ]
   call x2%print()

   x3%x = [ 3, 2, 1 ]
   call x3%print()

   stop

end program p

Upon execution,

  this%x =  1 2
  this%x =  3 2 1
Press any key to continue . . .

 

It's unclear from your example why you need include files at all; while the include files have some benefits, I do know from experience with several large project teams how they can also be a bane.  It's better if they're only used when truly needed, but your example doesn't make a case for it.

0 Kudos
IanH
Honored Contributor III
3,250 Views

FortranFan wrote:

It's totally unclear what point you're trying to make: either your example fails to reflect it or you're making it more complicated:

Consider the case where the type parameter has to be a kind type parameter - e.g. use it as a kind parameter for a component or a component initializer.  Consider also what the likely implementation (memory layout) of the type looks like or what has to happen if you want to do compile time specialisation of a particular (one of many) parameterisation.

No one (well, I don't at least) likes using INCLUDE, but "given ... the capability of the language today" or "current Fortran limitations", that's what having multiple identical-at-source-token-level specific procedure implementations for a particular kind-parameterised type (which includes all the intrinsic types!) involves (or lots of source duplication).

 

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

IanH wrote:

 ..

Consider the case where the type parameter has to be a kind type parameter - e.g. use it as a kind parameter for a component or a component initializer.  Consider also what the likely implementation (memory layout) of the type looks like or what has to happen if you want to do compile time specialisation of a particular (one of many) parameterisation.

No one (well, I don't at least) likes using INCLUDE, but "given ... the capability of the language today" or "current Fortran limitations", that's what having multiple identical-at-source-token-level specific procedure implementations for a particular kind-parameterised type (which includes all the intrinsic types!) involves (or lots of source duplication).

Oh, I am fully aware of that.  The actual implementation for the trouble incident related to this post (https://software.intel.com/en-us/forums/topic/536577) is indeed based on include files (much to my chagrin). but alas the Intel compiler still has several outstanding problems with parameterized derived types and that is seriously hurting me in my attempts to use this Fortran 2003 feature.

Where I've problem with the example shown in Quote #6 where the need for include files appears questionable, at least to me.  I also have an issue with the suggestion by OP to use kind parameter as length type (Quote #5) and use it for procedure resolution: I fail to see the need for it and I think the case the OP presents can be made so much simpler (Quote #7).

My instinct suggests the use of kind parameter as length type and use it for procedure resolution might be a practice fraught with danger and would like to bring out more discussion about it rather than being silent which may then lead to it quietly becoming "accepted" coding practice in some circles.

0 Kudos
IanH
Honored Contributor III
3,250 Views

FortranFan wrote:
My instinct suggests the use of kind parameter as length type and use it for procedure resolution might be a practice fraught with danger and would like to bring out more discussion about it rather than being silent which may then lead to it quietly becoming "accepted" coding practice in some circles.

What danger?  Be specific.

Do you object to people using named constants to specify a dimension of a local array?  Do you object to generic procedure resolution on the basis of the kind of an argument of intrinsic type?  Practically they are the same practices.

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

IanH wrote:

..

What danger?  Be specific.

Do you object to people using named constants to specify a dimension of a local array?  Do you object to generic procedure resolution on the basis of the kind of an argument of intrinsic type?  Practically they are the same practices.

Since when did I allude any opposition to named constants or generic procedure resolution, etc.?

I don't know how much simpler can I make it.  All I'm saying is:

   ..
   
   !.. Why do this?
   type, public :: kt(k)
      integer, kind :: k
      integer :: x(k)
   end type kt
   
   !.. When one can do this?
   type, public :: lt(n)
      integer, len :: n
      integer :: x(n)
   end type lt
   
   ..

Quote #5 and Quote #6 by the OP are unclear on this point.  What is the advantage of having a type kt versus lt since no generics with respect to data kind is really in play?  (but please: don't give me the example in Quote #6)  Are there repercussions if an appreciable crowd starts using kind type as a substitute for length type?  (Would Dr Fortran approve?!)  For example, what can go wrong when types are getting extended and in the extensions, a kind parameter used as length in parent types gets used indeed as kind in children.  May be there is nothing to worry in all this, I'd just like to have a healthy discussion and understand.

0 Kudos
IanH
Honored Contributor III
3,250 Views

FortranFan wrote:

Quote:

IanH wrote:

 

..

What danger?  Be specific.

Do you object to people using named constants to specify a dimension of a local array?  Do you object to generic procedure resolution on the basis of the kind of an argument of intrinsic type?  Practically they are the same practices.

 

 

Since when did I allude any opposition to named constants or generic procedure resolution, etc.?

I don't know how much simpler can I make it.  All I'm saying is:

   ..
   
   !.. Why do this?
   type, public :: kt(k)
      integer, kind :: k
      integer :: x(k)
   end type kt
   
   !.. When one can do this?
   type, public :: lt(n)
      integer, len :: n
      integer :: x(n)
   end type lt
   
   ..

Quote #5 and Quote #6 by the OP are unclear on this point.  What is the advantage of having a type kt versus lt since no generics with respect to data kind is really in play?  (but please: don't give me the example in Quote #6)  Are there repercussions if an appreciable crowd starts using kind type as a substitute for length type?  (Would Dr Fortran approve?!)  For example, what can go wrong when types are getting extended and in the extensions, a kind parameter used as length in parent types gets used indeed as kind in children.  May be there is nothing to worry in all this, I'd just like to have a healthy discussion and understand.

A crude analogy can be made between named constants and kind type parameters, and [dummy] variables and length type parameters in terms of their restrictions and flexibility of use.  In the same fashion that it isn't appropriate to blanket exclude the used of named constants in dimension specifications for local variables, it isn't appropriate to blanket exclude the use of kind type parameters from dimension specifications of type components. 

Similarly, procedure disambiguation on the basis of the kind of an intrinsic type is widely accepted - there seems little reason to exclude procedure disambiguation on the basis of the kind of a derived type.

While noting my previous comment about my opinion of the relative utility of kind type parameters (with the language as it is today :( ) and length type parameters, the language feature that is appropriate obviously depends on the requirements of the particular application.  The example in post #6 is close to one of the canonical examples of the use of kind parametrised types, if you extrapolate the use case a little.

Consider an application that needs to store and work on positions or displacements for objects.  At compile time, it is known for certain types of object whether the position is two dimensional or three dimensional (for some types of object you might be considering a position on a plane through three dimensional space, for other types of object you are considering the position of that type of object in three dimensional space).  Pre-PDT's, you would write two types - one for the two dimensional case:

TYPE :: Position2D
  REAL :: ordinates(2)
CONTAINS
  PROCEDURE, PRIVATE :: Displacement => p2d_Displacement
  GENERIC :: OPERATOR(-) => Displacement
END TYPE Position2D

FUNCTION p2d_Displacement(to, from) RESULT(disp)
  TYPE(Position2D), INTENT(IN) :: to
  TYPE(Position2D), INTENT(IN) :: from
  TYPE(Position2D) :: disp
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION p2d_Displacement

and one for the three dimensional case, which looks very much like the two dimensional case:

TYPE :: Position3D
  REAL :: ordinates(3)
CONTAINS
  PROCEDURE, PRIVATE :: Displacement => p3d_Displacement
  GENERIC :: OPERATOR(-) => Displacement
END TYPE Position3D

FUNCTION p3d_Displacement(to, from) RESULT(disp)
  TYPE(Position3D), INTENT(IN) :: to
  TYPE(Position3D), INTENT(IN) :: from
  TYPE(Position3D) :: disp
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION p3d_Displacement

If in your code you then had something like:

TYPE(Position2D) :: x = Position2D([1.0, 2.0])
TYPE(Position3D) :: y = Position3D([1.0, 2.0, 3.0])
TYPE(Position3D) :: z
z = x - y

the compiler will rightfully complain - because you are trying to carry out an operation on mismatching types and there is no matching specific procedure.

If the additional typing associated with the two types annoyed you, you might be tempted to use INCLUDE (perhaps with implicit typing tricks) to reduce the duplication of source; or you might head in completely the opposite direction and generalize things using an allocatable component:

TYPE :: PositionAlloc
  REAL, ALLOCATABLE :: ordinates(:)
CONTAINS
  PROCEDURE, PRIVATE :: Displacement => pos_alloc_Displacement
  GENERIC :: OPERATOR(-) => Displacement
END TYPE PositionAlloc

FUNCTION pos_alloc_Displacement(to, from) RESULT(disp)
  TYPE(PositionAlloc), INTENT(IN) :: to
  TYPE(PositionAlloc), INTENT(IN) :: from
  TYPE(PositionAlloc) :: disp
  IF (SIZE(to%ordinates) /= SIZE(from%ordinates)) STOP 'Dim mismatch'
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION pos_alloc_Displacement

But now you've turned a compile time check of a programming error into a run time check (or introduced the possibility of other programming mistakes going undetected), plus the Fortran processor will invariably have to use intermediate descriptors for the components (which may have performance implications), plus some other incidental downsides such as no longer being able to use useful structure constructors in constant expressions.  The type is inherently more flexible, but you pay for that flexibility and that is flexibility you don't need.  Maybe you go this way, maybe you don't - it depends.

The introduction of kind parametrised types is reasonably straight forward for the two separate type case - you get to lose a type definition.

TYPE :: PositionKind(dim)
  ! dim = 2 for 2D, 3 for 3D.
  INTEGER, KIND :: dim
  REAL :: ordinates(dim)
CONTAINS
  PROCEDURE, PRIVATE :: posk_2_Displacement
  PROCEDURE, PRIVATE :: posk_3_Displacement
  GENERIC :: OPERATOR(-) => posk_2_Displacement, posk_3_Displacement
END TYPE PositionKind

FUNCTION posk_2_Displacement(to, from) RESULT(disp)
  TYPE(PositionKind(2)), INTENT(IN) :: from
  TYPE(PositionKind(2)), INTENT(IN) :: to
  TYPE(PositionKind(2)) :: disp
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION posk_2_Displacement

FUNCTION posk_3_Displacement(to, from) RESULT(disp)
  TYPE(PositionKind(3)), INTENT(IN) :: from
  TYPE(PositionKind(3)), INTENT(IN) :: to
  TYPE(PositionKind(3)) :: disp
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION posk_3_Displacement

Relative to the two separate type case, there are no downsides as far as I can tell - everything that was compile time checkable still is and implementation is likely to be using "direct" descriptorless components without additional runtime overhead.

But you've still got that inane repetition of the same (bar the parameter value) source token sequence.  All you've saved, without include tricks, is the source for a type definition, plus made things a bit neater in terms of the namespace associated with the parametrised type.  It obviously depends on the situation, but most of the time my type definitions are tiny compared to the definitions of the procedures that work with the types.  This relatively small saving in source is why I think kind type parameters are of marginal value - relative to what you would have used without that feature being available.  Now they are available you use them, but it isn't going to change your world.

(If you do use include tricks to reduce the amount of duplicated source, there is a further benefit in that there is even less variation from procedure body to body now for different parametrizations, but ideally you wouldn't have to use INCLUDE - the language would have generic programming features that allowed you to generate the parametrisations of the procedures as required.  If this language gap was removed, kind parameters would be awesome too.)

With length type parameters you have something that is along the lines of the allocatable component option, but with less of the drawbacks.

TYPE :: PositionLen(dim)
  ! dim = 2 for 2D, 3 for 3D.
  INTEGER, LEN :: dim
  REAL :: ordinates(dim)
CONTAINS
  PROCEDURE, PRIVATE :: Displacement => posl_Displacement
  GENERIC :: OPERATOR(-) => Displacement
END TYPE PositionLen

FUNCTION posl_Displacement(to, from) RESULT(disp)
  TYPE(PositionLen(*)), INTENT(IN) :: from
  TYPE(PositionLen(*)), INTENT(IN) :: to
  TYPE(PositionLen(from%dim)) :: disp
  IF (from%dim /= to%dim) STOP 'Dim mismatch'
  disp%ordinates = to%ordinates - from%ordinates
END FUNCTION posl_Displacement

You still don't have compile time checking of dimension mismatches and the underlying implementation will still likely use a descriptor of sorts for the component, but you are no longer restricted around use of useful structure constructors in constant expressions.  It doesn't show in this simple example with one component, but in the case where you have multiple components that all have a size (or whatever) derived off the one parameter, you now have a type that is a better description of the data that it is meant to store (there is only one "length"), versus the case where multiple components are allocatable but allocated to the same size (they all store their own length, and will not be considered to have the same length in the general case).  It is this latter aspect in particular why I think length type parameters are a very useful addition to the language - the closer the description in-source of something is to the actual characteristics of the thing being described by the source, the better.

BUT the length parameter case isn't perfect - you are still buying flexibility that you don't need, and there is still some cost associated with that flexibility.  It's far better than the equivalent pre-PDT allocatable component option was, but is it better than the kind parameter version?  I do like compile time checking of things, and the constantness of the kind parametrisation is a better fit to the constantness of the relevant dimensionality of positions in the actual problem.  Maybe you go this way, maybe you don't - it depends...

(Code snippets above  head compiled - there are probably errors but hopefully they make some sense.)

0 Kudos
Lorri_M_Intel
Employee
3,250 Views

Back to the OP's original problem.  (Is that the OP's OP?)

The bug in this program is provoked by the parameter being in a module, because if you put everything together in the same module it's fine.

internal tracking id: DPD200367065

Finally a comment about using KIND parameters vs LEN parameters as array bounds.   Because the LEN parameter can be *anything* at the time a derived type instance is created, there is a lot of overhead required to support them at various times of the host variable's life-cycle thru the code (instantiation, allocation, deallocation, being passed to other routines, etc).   There are lots of cases when LEN parameters are useful, but if your problem is defined in such a way that using KIND will work, that would result in simpler code.

                --Lorri

 

 

 

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

Thanks much Lorri and Ian for your comments.

Lorri,

Re: your comment on KIND vs LEN parameters in Quote #13, will it be possible for you to analyze an idea that I've had ever since I first read about parameterized derived types and see if a) whether Intel compiler implementation can result in simpler code if the standard were to be modified in a future revision to include some coder-specified "limits" on LEN parameters and b) if you feel my idea has some merit, can you please discuss with your colleagues (Steve, Stan Whitlock) and consider tabling it at some future standards discussion?  The idea is along the following lines (please don't worry about syntax; it can be whatever):

   type :: t1(l)
      !.. this says the length values can only be those on the list
      integer, len :: l = [ l1, 12, .., ln ]
      integer :: x(l)
   end type t1
   
   type :: t2(l)
      !.. This says the length values have to be in the range of
      !   l_low to l_up
      integer, len :: l = l_low:l_up
      integer :: x(l)
   end type t2
   

Is the above something that is doable in the Intel Fortran compiler and if so, can the Fortran standard ever be extended to have something along the following lines?  If something like were available, then can IanH's PositionKind example gain compile-time benefits too if the coder were to declare the type with an allowed list of dimensions to be, say, just 2 and 3?

Thanks,

0 Kudos
Steven_L_Intel1
Employee
3,250 Views

This suggestion would have to wait for whatever standard comes after F2015, as the features are locked down for this one. Given there's little overall usage of PDTs at the moment, I doubt there's much stomach for discussing enhancements such as this. Theoretically, the compiler might be able to make use of the information in deciding whether it's profitable to vectorize or paralellize.

While the syntax proposed here - and I know it's just a conversation starter - is unambiguous (I think), my guess is that there would be qualms about using initialization syntax with things that are clearly not initializers. Fortran is adding "clauses" (think BIND and RESULT), so maybe something like:

integer, len :: l, only(l1,l2,l3)
...
integer, len :: l, range(l_low:l_up)

would be workable. Just a thought.

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

Steve Lionel (Intel) wrote:

This suggestion would have to wait for whatever standard comes after F2015, as the features are locked down for this one. Given there's little overall usage of PDTs at the moment, I doubt there's much stomach for discussing enhancements such as this. Theoretically, the compiler might be able to make use of the information in deciding whether it's profitable to vectorize or paralellize.

While the syntax proposed here - and I know it's just a conversation starter - is unambiguous (I think), my guess is that there would be qualms about using initialization syntax with things that are clearly not initializers. Fortran is adding "clauses" (think BIND and RESULT), so maybe something like:

integer, len :: l, only(l1,l2,l3)
...
integer, len :: l, range(l_low:l_up)

would be workable. Just a thought.

Steve, thanks much for chiming in - I appreciate it greatly.  I like your syntax; note for me, what's important is the concept i.e., of being able, as a coder, to impose some limits on the length parameter in a PDT.  I'm completely open-minded on the syntax.  Something like what you propose will be a very valuable improvement to the PDT feature, I think.  And if that can result in better code, both for the user (see IanH's comments in Quote #12 such as compile-time checks) and for the compiler (per Lorri's comments in Quote #13 re: overhead that gets created), then that's a win-win.  If Intel can "table" this idea for discussion at some future standards discussion, I'll be thrilled.

0 Kudos
IanH
Honored Contributor III
3,250 Views

FortranFan wrote:

Quote:

Steve Lionel (Intel) wrote:

 

This suggestion would have to wait for whatever standard comes after F2015, as the features are locked down for this one. Given there's little overall usage of PDTs at the moment, I doubt there's much stomach for discussing enhancements such as this. Theoretically, the compiler might be able to make use of the information in deciding whether it's profitable to vectorize or paralellize.

While the syntax proposed here - and I know it's just a conversation starter - is unambiguous (I think), my guess is that there would be qualms about using initialization syntax with things that are clearly not initializers. Fortran is adding "clauses" (think BIND and RESULT), so maybe something like:

integer, len :: l, only(l1,l2,l3)
...
integer, len :: l, range(l_low:l_up)

would be workable. Just a thought.

 

 

Steve, thanks much for chiming in - I appreciate it greatly.  I like your syntax; note for me, what's important is the concept i.e., of being able, as a coder, to impose some limits on the length parameter in a PDT.  I'm completely open-minded on the syntax.  Something like what you propose will be a very valuable improvement to the PDT feature, I think.  And if that can result in better code, both for the user (see IanH's comments in Quote #12 such as compile-time checks...

PROGRAM RollTheDice
  IMPLICIT NONE
  TYPE :: t(l)
    INTEGER, LEN, ONLY(1,2,3) :: l
  END TYPE t
  REAL :: r
  CALL RANDOM_NUMBER(r)
  CALL sub(FLOOR(r*5.0) + 1)
CONTAINS
  SUBROUTINE sub(l)
    INTEGER, INTENT(IN) :: l
    TYPE(t(l)) :: thing
    ! fun and games with `thing` here...
  END SUBROUTINE sub
END PROGRAM RollTheDice

What happens?

 

(edit: beyond a diagnostic for a missing declaration...)

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

IanH wrote:

 ..

PROGRAM RollTheDice
  IMPLICIT NONE
  TYPE :: t(l)
    INTEGER, LEN, ONLY(1,2,3) :: l
  END TYPE t
  REAL :: r
  CALL RANDOM_NUMBER(r)
  CALL sub(FLOOR(r*5.0) + 1)
CONTAINS
  SUBROUTINE sub(l)
    INTEGER, INTENT(IN) :: l
    TYPE(t(l)) :: thing
    ! fun and games with `thing` here...
  END SUBROUTINE sub
END PROGRAM RollTheDice

What happens?

 

(edit: beyond a diagnostic for a missing declaration...)

Also, one should keep this in mind (a bad state as of today):

PROGRAM RollTheDice
  IMPLICIT NONE
  TYPE :: t(l)
    INTEGER, LEN :: l
    integer :: x(l)
  END TYPE t
  REAL :: r
  CALL RANDOM_NUMBER(r)
  CALL sub(FLOOR(r))
CONTAINS
  SUBROUTINE sub(l)
    INTEGER, INTENT(IN) :: l
    TYPE(t(l)) :: thing
    print *, " this%x = ", thing%x
  END SUBROUTINE sub
END PROGRAM RollTheDice

 

So what are the positive ways to build on the idea in Quote #16 and improve upon it? 

 

 

0 Kudos
IanH
Honored Contributor III
3,250 Views

(What's the issue with that example?)

I think it depends on what you are trying to achieve.    Fundamentally a length type parameter is a runtime concept (in the general case), so if you want compile time checking of values you are out of luck.  Your options are:

  1. Give up compile time checking and make this a run time assertion of some form.  This then blurs with ideas for a more general feature for runtime assertions - which might have the objective of being a debugging aid (the program will insert appropriate tests for a violation of this condition and report via something similar to ERROR STOP) .OR. a compiler optimization aid (I, the programmer, solemly promise to never violate these conditions, if I do actually violate them I accept that the program might do very bad things to my cat, so dear compiler please optimize your little heart out).   Depending on how the feature was designed, note ".OR." might be ".XOR.".  It may also blur into feature requests for runtime exceptions in the language. 
  2. Retain compile time checking and give up on applying the feature to length parameters - instead make it applicable only to kind parameters.  This then blurs into a general static assertion facility (you can actually do some forms of static assertion now, but depending on details the syntax and resulting diagnostic are rather obscure).  It might also blur into a feature around a more general way of statically specifying constraints to the values that certain objects might hold - consider enumerations, real values that must be positive, etc.
  3. Just give up and go and work on some other feature.  (Hopefully generic programming related.)

Examples of source of static assertion of kind parameters, which just turned out to be examples of ifort compiler bugs :( :

PROGRAM ThisShouldNotWorkButItDoes
  IMPLICIT NONE
  
  TYPE :: t(k, dummy)
    ! Say the value of k must be between 1 and 100.  We want a compiler 
    ! diagnostic of some form if this is not the case.
    INTEGER, KIND :: k
    ! Try and create an integer of invalid kind.
    INTEGER(MERGE(KIND(1),-1,k >= 1 .AND. k <= 100)), KIND :: dummy = 0
  END TYPE t
  
  TYPE(t(55)) :: a      ! Ok.
  TYPE(t(101)) :: b     ! We SHOULD get a diagnostic!
  
  ! What????
  PRINT *, a%k, MERGE(KIND(1), -1, a%k >= 1 .AND. a%k <= 100)
  PRINT *, b%k, MERGE(KIND(1), -1, b%k >= 1 .AND. b%k <= 100)
  PRINT *, KIND(b%dummy)    ! How....???
END PROGRAM ThisShouldNotWorkButItDoes

 

>ifort /warn:all /stand "2015-03-04 static-assert-1.f90" && "2015-03-04 static-assert-1.exe"
Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 15.0.2.179 Build 20150121
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

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

"-out:2015-03-04 static-assert-1.exe"
-subsystem:console
"2015-03-04 static-assert-1.obj"
          55           4
         101          -1
           4

Maybe?

PROGRAM ThisShouldWorkButItDoesNotWork
  IMPLICIT NONE
  
  TYPE :: t(k, dummy, dummy_kind)
    ! Say the value of k must be between 1 and 100.  We want a compiler 
    ! diagnostic of some form if this is not the case.
    INTEGER, KIND :: k
    INTEGER, KIND :: dummy_kind = MERGE(-1,KIND(1),k >= 1 .AND. k <= 100)
    INTEGER(dummy_kind), KIND :: dummy = 0
  END TYPE t
  
  TYPE(t(55)) :: a      ! This SHOULD be ok.
!  TYPE(t(101)) :: b    ! This shouldn't (but it is commented out).
END PROGRAM ThisShouldWorkButItDoesNotWork
>ifort /warn:all /stand "2015-03-04 static-assert-2.f90" && "2015-03-04 static-assert-2.exe"
Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 15.0.2.179 Build 20150121
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

2015-03-04 static-assert-2.f90(12): error #6683: A kind type parameter must be a compile-time constant.   [MERGE]
  TYPE(t(55)) :: a      ! This SHOULD be ok.
^
2015-03-04 static-assert-2.f90(12): remark #7712: This variable has not been used.   
  TYPE(t(55)) :: a      ! This SHOULD be ok.
-----------------^
compilation aborted for 2015-03-04 static-assert-2.f90 (code 1)

Is it MERGE in constant expressions that is playing up?

PROGRAM ThisWorksButGetsASillyWarningWithStand
  IMPLICIT NONE
  
  INTEGER, PARAMETER :: k = 101
  INTEGER, PARAMETER :: dummy_kind  &
      = MERGE(KIND(1),-1,k >= 1 .AND. k <= 100)
  ! We get the diagnostic as expected if this is uncommented.
!  INTEGER(dummy_kind), PARAMETER :: dummy = 0
END PROGRAM ThisWorksButGetsASillyWarningWithStand
>ifort /warn:all /stand "2015-03-04 static-assert-3.f90" && "2015-03-04 static-assert-3.exe"
Intel(R) Visual Fortran Intel(R) 64 Compiler XE for applications running on Intel(R) 64, Version 15.0.2.179 Build 20150121
Copyright (C) 1985-2015 Intel Corporation.  All rights reserved.

2015-03-04 static-assert-3.f90(6): warning #7374: F2003 standard requires all arguments be of the same type and same kin
d type parameter.
      = MERGE(KIND(1),-1,k >= 1 .AND. k <= 100)
----------------------^
Microsoft (R) Incremental Linker Version 10.00.40219.01
Copyright (C) Microsoft Corporation.  All rights reserved.

"-out:2015-03-04 static-assert-3.exe"
-subsystem:console
"2015-03-04 static-assert-3.obj"

I choose option three - "I give up."

0 Kudos
FortranFan
Honored Contributor III
3,250 Views

IanH wrote:

(What's the issue with that example?)

I think it depends on what you are trying to achieve.    Fundamentally a length type parameter is a runtime concept (in the general case), so if you want compile time checking of values you are out of luck.  ..

I have no idea what any of your comments mean and what exactly you're trying to convey, whether a severe opposition to suggestions in Quote #14 and Steve's followup to Quote #15 or aspects that compiler writers need to take into account.  As far as I'm concerned if there's will, there will be a way.  I think PDTs are valuable enough that standard-bearers should rethink and consider further improvement along the lines of being able to use kind parameters without a practical need for include files, being able to specify some limits on type parameters, etc..

And from what I see, if such a "limits" feature can be implemented for the type parameters in PDTs, my sense is generated code (per Quote #13) can be made simpler and open up possibilities for optimization, vectorization/parallelization, as mentioned by Steve.  In addition, coders can get some value out of it in the form of checks: it may be compile-time in some coding situations, run-time in other scenarios, AND perhaps static analysis in other - nothing wrong, to me, a lot of aspects of Fortran arrays and allocatables and pointers appear to be in this mode (if anyone disagrees, well so be it; noone will change my views on it and I won't be drawn further into debating that).  And another advantage I see with the "limits" idea is that perhaps it'll ensure kind parameters get used for kinds and length parameters for object lengths; not the substitution of kind for length as suggested originally in this thread, a questionable practice it still appears to me.

I hope Intel Fortran team can get fully on board with this "limits" idea and take it up with the standards committee for discussion at an appropriate time post 2015 standards development; and I hope Quote #17 and #19 are not meant for discouragement.

 

 

0 Kudos
IanH
Honored Contributor III
3,120 Views

FortranFan wrote:

Quote:

IanH wrote:

 

(What's the issue with that example?)

I think it depends on what you are trying to achieve.    Fundamentally a length type parameter is a runtime concept (in the general case), so if you want compile time checking of values you are out of luck.  ..

 

 

I have no idea what any of your comments mean and what exactly you're trying to convey, whether a severe opposition to suggestions in Quote #14 and Steve's followup to Quote #15 or aspects that compiler writers need to take into account.  ...

Neither, really (certainly not the first of those).  I was just exploring what this sort of feature would look like and how it would integrate into the rest of the language (which is something that anyone involved with the language, not just compiler writers, needs to take into account).

By "runtime concept" I mean that the compiler doesn't always know the value of a length parameter of an object, in the general case, at compile time.  For a dummy argument the length parameter might be assumed, for a local variable it might be specified by another variable not known at compile time (that is - the object with the length type parameter is an automatic object), for a deferred parameter in an allocatable or pointer object it won't be known until the object is allocated or associated.  Because the value isn't known, in the general case, at compile time, you can't check it, in the general case, at compile time!

That's ok - perhaps you were describing a run time checking feature?  Hence my point one, exploring what that could look like and how it compares to many of the other ideas for the language that have been floating around in recent years.

Maybe that's not ok - compile time checks are very handy for ensuring program correctness ahead of program use.  Hence my point two (which erroneously mixes in elements of point one)...

(Maybe it's all too hard (or there are higher priority features to work on - there are things that I would like to see work on ahead of this) - point three!)

And another advantage I see with the "limits" idea is that perhaps it'll ensure kind parameters get used for kinds and length parameters for object lengths; not the substitution of kind for length as suggested originally in this thread, a questionable practice it still appears to me.

I don't understand why you see this practice as questionable.  I think whether something is a length parameter or a kind parameter should be more a function of its "must be known at compile time"/"may be specified at run time" nature than where it is specifically used, current language shortfalls aside.  That's what #12 was trying to explore.

0 Kudos
Reply