Compiler error with continuation in array constructor

I made some fake data to work with in my main program and I placed it in a module for sharing the data with the program. It was 50 data points with 50 values of double precision data, and I was using reshape to reshape the data to (50,2). I have attached my code and the error. I am not near any continuation limit so I don’t know what the problem is. You can see in the image that it gives me an error on the 4th line of data, which is the 6th continuation line. Will you please take a look and tell me what the problem is and how to fix it?

Actually since I am a new user I can only post one media pic per topic. Below is my error, it is showing an error at the space between the last number on the line and the & character.

12 | -2.24489795918368 -1.83673469387756 -1.42857142857143 -1.02040816326531 -0.61224489795919 -0.204081632653067 &

And as a follow up question. Is this a recommended way to share data with the program without clogging up the beginning of my code with a bunch of data?

@William_S,

Welcome to the forum!

Re: “You can see in the image that it gives me an error on the 4th line of data,” can you share some details on the specific error you encounter? Is it with gfortran compiler and something along the likes of, “Error: Without padding, there are not enough elements in the intrinsic RESHAPE source at (1) to match the shape?”

@William_S ,

If your error is indeed, “Error: Without padding, there are not enough elements in the intrinsic RESHAPE source at (1) to match the shape?," then you have syntax error with

  1. missing comma separator following each element,
  2. use of an integer literal 10 when the expected literal is of REAL type with a decimal (period).

Re: “Is this a recommended way to share data with the program …,” what you show is alright unless your list of data grows prohibitively long and varying in which case a data file or a database might be something you may want to consider.

If your list of values is on the order of a manageable number (you show 50 x 2 = 100), then I suggest the following edits: note it is shown below with 4 values only for illustration purposes.

module Values_m

   implicit none

   integer, parameter :: WP = selected_real_kind( p=12 )

   real(kind=WP), parameter :: Values(*) = [    &
       -10.0_wp, -9.59183673469388_wp, -9.18367346938776_wp, -8.77551020408163_wp ]

   integer, parameter :: N = size(Values)/2
   real(kind=WP), dimension(N,2) :: mydata = reshape( Values, shape=shape(mydata) )

   save

end module Values_m

That is,

  1. Use a defined KIND constant (see WP in the above snippet) toward the precision of your floating-point values and data types instead of a hard-wired kind of 8 that is not portable,
  2. Use a named constant, say Values in the above snippet, of rank-1 where the array constants inform the program about the shape, whether 100 or whatever,
  3. Note the _wp suffix on each element. You can look up a suitable Fortran reference, however the suffix helps you with precision with situations where the literal value is not exactly representable with the default precision of REAL (usually 6, or colloquially single precision) with your compiler,
  4. Then work off of the rank-1 array named constant to construct the data object of interest to you, as you call it mydata.
  5. Try not to repeat the information specification such as (50,2) in two (or more) places; rather, enter the information once and let the program then build out the rest.

Now, if your data are not expected to be modified by your program, then consider applying the PARAMETER attribute to your mydata object as well.

Also, the DIMENSION attribute can seem verbose, so consider whether you like specifying the shape of your object side-by-side with its name e.g.,

   .
   real(kind=WP) :: mydata(N,2) = reshape( .. )

Dang I feel dumb, no commas. I could not see it. Thanks.

Also note @FortranFan’s example of changing -9.59183673469388 to -9.59183673469388_wp, as with F90+, -9.59183673469388 in a data statement for real(8) is treated as a 32-bit real constant, so truncateing it to -9.591837.
Only Modern Fortran would have this in their standard !
Yet we will probably have complaints that mydata is implicitly SAVE.

Readers, re: “Only Modern Fortran would have this in their standard !,” please see this proposal and please think over it and post your thumbs down or up depending on your needs and understanding:

I too think the standard revision termed Fortran 90 itself missed a huge trick by leaving a floating-point literal constant without a KIND suffix as default REAL type with no standard option to specify otherwise.

The above proposal is a good way, I believe, to address the gap and it covers other intrinsic types also, so that is a good approach.

Now this proposal is on the list of options that may get included in Fortran 202Y. But there is always great risk of the slip between the cup and the lip kind, hence it is good when more and more practitioners review proposals and give their up/down feedback.

Separately, a MODULE entity is intended to be SAVEd, it can be kinda viewed as a “global variable” anyway. Thus the “implied SAVE” with module entities or objects in main programs is not of any objection.

The complaint about the “implied SAVE” semantics pertains to local variables using definition along with declaration form in subprograms. It’s this “bug” in the standard masquerading as a feature that is highly objectionable.

A huge trick ? To me it has been an unnecessary and misguided destruction of optimum precision.

I do not think your suggestion of Default Kinds is the way to go, but my preference for simplifying the language is rarely supported.

Lahey Fortran 95 ver 5.55j (2000) did not support the Fortran 90 standard regarding precision of real constants. It stores all real constants (such as 0.1 or -9.59183673469388) to 64-bit (probably 80-bit) precision.
Unfortunately, this was at a time when 80-bit registers were being replaced by 64-bit SSE simd instructions, so the reasons for loss of 64-bit calculation precision were multiple.

A “smart” Fortran optimising compiler should also be allowed to recognise the precision provided in Fortran code and do it’s best.
Compilers should be able to correctly interpret the following statements and provide what was intended, rather than the ridiculous “gotcha” that the F90+ standards and FortranFan require.
Real(8) x
Integer(8) jj
x = -9.59183673469388
jj = 4500000000 ! or
jj = 2**32

As for integer constants >= 2**32, a 64-bit Fortran compiler that cannot reasonably interpret this is not fit for purpose.

I wonder what Backus or perhaps McCracken would have thought regarding 64-bit integer constants !

This statement by @JohnCampbell is a good example of what is meant by everything is yellow to the jaundiced eye!

First of all, FortranFan does not “require” anything in this particular context, to each their own!

The fact is the Fortran standard since its early days has treated a floating-point constant with a real part and without an exponent D as default real; and starting with Fortran 90, without a KIND suffix as default real. Within the context of the standard, about the only other way I can figure out a way to inform the processor of the default kind or the kind of a literal-constant is as shown in the above proposal. However everyone is free to make other better proposals.

Outside of the standard now, a practitioner can look to the compiler of their choice to help them e.g., gfortran users can look at -fdefault-xx options and if any of them can help, say perhaps -fdefault-real-8. Naturally this is not a portable approach. Lahey (though no longer in business to offer any new compiler versions) may do things differently from any other compiler.

In the context of the original post and with the modified snippet I provide here, should this proposal be part of a future standard, the code can look like so:

module Values_m

   implicit none

   integer, parameter :: WP = selected_real_kind( p=12 )

   default real ( kind=WP )  !<-- proposed feature

   ! see the listing of constants below, the "_wp" suffix not needed
   ! KINDs of constants based on previous statement with "default"
   real(kind=WP), parameter :: Values(*) = [    &
       -10.0, -9.59183673469388, -9.18367346938776, -8.77551020408163 ]

   integer, parameter :: N = size(Values)/2
   real(kind=WP), dimension(N,2) :: mydata = reshape( Values, shape=shape(mydata) )

   save

end module Values_m

Readers can look at the above link for the proposal for further details and of course, the expectation must always be that the J3 standard committee will ultimately flesh out all the details and iron out any wrinkles so that a feature implementable by a conforming processor is developed.

However the point with the default statement is the default KINDs of intrinsic types are explicitly specified for the processor for a program unit / scope in a standard way for all the compilers. The proposed feature extends to the KIND of results of intrinsic functions, e.g., SIZE which is indeed another “gotcha” in the standard.

Would this also change the default integer and logical so that they all remain the same regarding storage sequence association?

Regarding the issue of default precision in general, I have mixed feelings about both the current situation and also the various proposals. I would note however that when values are read with i/o statements, they always retain the precision of the destination entity, even if E or D exponents are used within the record. That is, an E exponent does not truncate the precision, and a D exponent does not extend it. And for other KIND values in f90+, there has never been a way to specify the KIND value within a record. That might be regarded as inconsistent with the way KIND values are used to specify constants within the source code itself. But on the other hand, I think it would be a big mess of inconsistency and nonportability if that were attempted.

I do not like the idea of always making a real constant acquire the highest precision supported by a compiler, whether that is REAL64, REAL80, REAL128, or REAL256. Although that does solve the problem of beginners inadvertently dropping bits, it means that programmers would lose control of the KIND values of intermediate results in expressions, making expression evaluations even more compiler dependent than they are now. And, of course, it would not be backward compatible with decades of conventions where the default real means exactly that, the default real precision. Backwards compatibility is important to many programmers working with legacy codes.

I don’t think it’s needed, since as I understand the proposal default real (kind=...) would not affect the declarations, but only the constants. By the way default real constants (kind=...) may be preferable.

1 Like

I had thoughts alone these lines and about changing the IMPLICIT statement to allow something similar. Not proposing it as an alternative to this proposal, but found this other related issue in the process. Is the following a ubiquitous compiler bug
or does the IMPLICIT statement not take the same options for TYPE as a declaration? For example:

program main
use, intrinsic :: iso_fortran_env, only : real_kinds,sp=>real32,dp=>real64,qp=>real128
implicit type(null) (a-h)
!implicit type(real) ( r)             ! <== valid type specification fails
!implicit type(real(kind=qp)) ( q )   ! <== valid type specification fails
type null
end type null
type(real) float
type(real(kind=qp)) quad

   float=1.0d0/3.0d0
   quad=1.0d0/3.0d0
   write(*,*)float,quad
   quad=1.0_qp/3.0_qp
   write(*,*)float,quad

end program main

It is strange to me that I can do implicit typing for user-defined types and intrinsic types of the default kind, but that every compiler I tried would not take the TYPE(REAL(KIND=QP)) syntax to allow specifying a default for intrinsics not of the default kind, which works fine on all the same compilers for variable declaration. Not sure if it is intentional or a very common bug.

proposal code I was playing with for reference
! this is currently valid
program main
use, intrinsic :: iso_fortran_env, only : real_kinds,sp=>real32,dp=>real64,qp=>real128
implicit integer (i-n)
implicit real (r), doubleprecision(d), type(blob) (z)
implicit type(null) (a-c,e-h,o-q,s-y)
type blob
   integer :: i
   integer :: j
   integer :: k
end type blob
type null
end type null
! this is OK for a variable but not in an implicit statement, which means only 
! intrinsics of default kind can be used ??? or is it a compiler bug in IMPLICIT ???
type(real(kind=qp)) quad
end program main
! So it seems relatively natural to allow IMPLICIT to be used for constants, just not
! 
! implicit statement should allow this syntax to allow other than default intrinsic kinds
!    implicit type(real(kind=dp)) (o-z)
! or maybe if :: is used to remove the conflicts, especially in fixed format, but this
! requires forward parsing if the kind= is not required:
!    implicit real(kind=dp) :: (o-z)
!
! an asterisk or underscore would indicate constants
!    implicit type(real(kind=dp)) (*)
! so even this would be allowed
!    implicit type(real(kind=qp)) (a-z*)
! but using both NONE and a default constant would obviously be desirable
! implicit none, type(doubleprecision) (*) 
! but it would be confusing as to whether that mean no doubleprecision constants were
! allowed without a type or whether floating point constants defaulted to doubleprecision
! not sure what this might mean though. Would that be useful or not?
! implicit type(blob) (*) 
! the biggest issue is perhaps what defining more than one for a floating point, integer, or character
! type, as * is not exclusive like letters are, so instead of * you might have to use some symbol name
! like real, integer, character. IMPLICIT never allowed (abc). It had to be (a-c) or (a,b,c) or even (a-b-c)
! but since multi-alphameric strings were not allowed, words like that would be OK.
! 
1 Like

@urbanjost ,

You can consider submitting a bug fix request with gfortran on this standard-conforming short reproducer that shows you how you can use the IMPLICIT statement currently:

   use, intrinsic :: iso_fortran_env, only : WP => real128
   implicit type(real(kind=WP))( m )
   type(real(kind=WP)) :: r
   print *, "kind(myreal) = ", kind(myreal), "; expected is ", kind(r)
end
C:\temp>gfortran -ffree-form -c p.f
p.f:2:4:

    2 |    implicit type(real(kind=WP))( m )
      |    1
Error: Unclassifiable statement at (1)

The output from the program with a conforming processor shall be (without any leading blanks):

 kind(myreal) = 16 ; expected is 16
1 Like