Type component with len attribute must be default integer kind

I need to create a parameterized derived type that contains two long arrays.

type my_type(n)
    integer(8), len :: n
    real(8) :: a(n) 
    real(8) :: b(n) 
end type

GFortran gives me this error message: component with LEN attribute must be default integer kind(4). How should I solve this issue?

I can work it around with allocatable arrays:

integer(8) :: n
  
type my_type
  real(8), allocatable :: a(:) 
  real(8), allocatable :: b(:) 
end type
  
type(my_type) :: x
      
allocate(x%a(n))
allocate(x%b(n))

It’s probably better to steer clear of PDTs if you are going to be using mainly gfortran.

1 Like

Does the LEN parameter have to be INTEGER(8)? Or would INTEGER(4) suffice?

Yes. I work with super long arrays.

@fortran4r , you may want to reconsider your use of a hard-wired number such as 8 for KINDs of intrinsic types.

This is more for any FOSS volunteer with GCC/gfortran willing to work in PDTs: the following snippet conforms and a standard-conforming compiler should help produce the output as shown:

   use, intrinsic :: iso_fortran_env, only : int64
   integer, parameter :: I8 = selected_int_kind( r=10 )
   type :: t1(n)
      integer(int64), len :: n = 0
   end type
   type :: t2(n)
      integer(I8), len :: n = 0
   end type
   type(t1) :: foo
   type(t2) :: bar
   print *, "kind(t1%n) = ", kind(foo%n)
   print *, "kind(t2%n) = ", kind(bar%n)
end

kind(t1%n) = 8
kind(t2%n) = 8

“the code most recently posted here” has been fixed. There was a markdown error, new line was missing following “‘’''Fortran” and it omitted the first line that had the ‘use’ statement.

Do you mean exactly this very output or just that it should compile and run OK? I hope the latter only, as the standard does not say anything about specific kind values, AFAIK.

But even if assume that the values are just number-of-bytes per single value. Would it be prohibited by the standard that an implementation (is it called processor in the modern, but weird to me, nomenclature?) has just one, 16-bytes integer kind? Or maybe two: 4B and 16B?

I personally think real(8) and integer(8) are very concise and expressive. In contrast, real(real64) and integer(int64) look very weird. Real already means real number, which makes real(real64) look redundant. If you use dp => real64, then it is difficult to find a similar alias for int64. Having both real(dp) and integer(int64) in a code looks inconsistent and weird.

PS: I and my colleagues only use GFortran, so I am not worried about code portability.

The standard obviously does not say anything about the KIND values themselves, the listing of ‘8’ will only be relevant to the processor that helped produce shown output.

Perhaps you should consider that others will use this website to pick up hints about correct use of Fortran and your use of a specific compiler’s idiom will make that job harder and help propagate a misunderstanding of the nature of KIND numbers.

You might also consider that people will be less inclined to comment on your posts if they have to convert your code snippets to standard Fortran.

3 Likes

I fully support @FortranFan and @themos comments on using hardwired literal values for kinds but just out of curiosity:

Are there (m)any modern compilers using kind values other than byte-length? From the abyss of my memory I can recall only old g77 compiler which used kind=1 for default, 2 for double length, 3 for 1-byte, 5 for half-length. But it was (a) just before the last dinosaur died, (b) not standard at all, just extension.

The NAG Fortran compiler supports three different kind numbering schemes, to help check that your code makes no unwarranted assumptions.

1 Like

What I frequently use for default kinds is,

module Constants_mod
    use iso_fortran_env
    integer, parameter :: IK => int32  ! default Integer Kind
    integer, parameter :: RK => real64 ! default Real Kind
    integer, parameter :: CK => real64 ! default Complex kind
end module

program
    use Constants_mod :: IK, RK
    integer(IK) :: var_IK
    real(RK) :: var_RK
    complex(CK) :: var_CK
end program

Why?

  1. avoids the use of non-standard non-portable notation.
  2. defines the universal default kinds across the entire codebase, such that the behavior of the codebase can be fully controlled from a single module.
  3. separates the default kind of complex from real. This may seem somewhat redundant, but it provides much finer control over what should be the default complex kind and what should be real kind across the codebase.

Even if some objects have to be non-default kind, it is likely much better to define those non-default kinds in a base module to be used elsewhere, like:

module Constants_mod
    use iso_fortran_env
    integer, parameter :: IK => int32 ! default Integer Kind
    integer, parameter :: IK8 => int8
    integer, parameter :: IK16 => int16
    integer, parameter :: IK32 => int32
    integer, parameter :: IK64 => int64
end module

Reasons are the same: if suddenly selected_integer_kind() or selected_real_kind() is to be used instead of iso_fortran_env kinds, this change of behavior only happens in a few lines of a single module (here Constants_mod), and nothing else in codebase needs to change.

I would never use integer(int32) or real(real64) where int32 or real64 belong to iso_fortran_env unless it is either a simple test, or int32 / real64 appear in precisely the same context as defined in the language, which is different from what most think.

True. The default in my writing is rather misleading (it was not meant to refer to standard default)

Here is Steve’s patch: PDT type parameters are not restricted to default integer, thanks @kargl!

Indeed, please keep submitting bugs to any compiler that you use.

Thanks @kargl for the patch and thanks @FortranFan for finding and reporting the bug in the first place! A fruitful combined effort.

(I think Harald Anlauf is not in this discourse but I’d like to thank him as well :slightly_smiling_face: )

Oh, my bad for selecting the wrong user to tag (with a subtly similar name).

1 Like

@epagone ,

Just catching up to this thread and noticed your comment.

I would have thought you were referring to this thread at comp,lang.fortran from Nov-Dec 2017: https://groups.google.com/g/comp.lang.fortran/c/NDE6JKTFbNU/m/YRtjs7ahBQAJ