Maximum number of continuation line `&`

I recently came across something unexpected about the continuation line character: `&`.

There is a hard limit of 19 (F77), 39 (F90), or 255 (F03) `&`-character per line (see the Intel forum or the wiki page). While this is usually sufficient, I found myself writing a small database of parameters using the data construct and ended up with 611 lines. The piece of code looked like this:

data(db(i), i = 1, n)/&
    item(‘item1’, 1.0_rp),&
    item(‘item1’, 2.0_rp), &
    item(‘item1’, 3.0_rp), &
    ...

Knowing this limit, is there a better way to create that database at compile time?

NB: I ended up using a 2D array using a chunk size as the second dimension, but I am open to more elegant solutions.

1 Like

Well, you could split up the assignment into chunks:

data (db(i), i = 1,200) / ... /
data (db(i), i = 201,400) / ... /
etc.

Perhaps not all that elegant, but it should work :slight_smile:

3 Likes

:thinking: . I should have thought about it. Thanks @Arjen.
That still requires some manual splitting, but that’s slightly better than what I was doing.

… thank goodness not all compilers are so picky at that :sweat_smile:

1 Like

That’s a lot of lines :sweat_smile: . Imagine splitting your 1000 lines into chunks of 39…
So gfortran allows at least 1000 &-characters as an extension. I tried and it only issues a warning when compiling with ```-std=f2008``` (or later).

Warning: Limit of 255 continuations exceeded in statement at (1)

For ifort, the limit is at 511. Are there any higher offers?

for better or worse, a single data statement does not need used to declare the values. You can use multiple data statements to fill portions.
The standard does require you not specify a value more than once, although extensions often allow this, I would strongly recommend following the rules as it is not portable and also requires the data to be filled in a particular order, and nothing in the standard says the data statements have to be used in the order declared.

The fact data statements are not required to fill their target can be considered a feature or a flaw. It is possible to accidently only partially fill the target when intending to fill it; leaving uninitialized values, but data statements are very versatile. You can easily fill in row-column order, use repeat modifiers, and so on.

program stuff
integer,parameter          :: rp=kind(1.0d0)
integer,parameter          :: n=3, m=8
character(len=*),parameter :: dt='(2(g0))'
type item
   character(len=20)       :: desc
   real(kind=rp)           :: value
end type item

! if values are easily computed this syntax might work
type(item)        :: db2(m)=[(item('item1',i*1.0_rp),i=1,m)]

type(item)        :: db(m)

! use multiple data statements
data(db(i), i = 1, n)/&
   item('item1', 1.0_rp), &
   item('item1', 2.0_rp), &
   item('item1', 3.0_rp)/

data(db(i), i = n+1, m)/&
   item('item1', 4.0_rp), &
   item('item1', 5.0_rp), &
   item('item1', 6.0_rp), &
   item('item1', 7.0_rp), &
   item('item1', 8.0_rp)/

   write(*,dt)db
   write(*,dt)
   write(*,dt)db2

end program stuff
item1               1.0000000000000000
item1               2.0000000000000000
item1               3.0000000000000000
item1               4.0000000000000000
item1               5.0000000000000000
item1               6.0000000000000000
item1               7.0000000000000000
item1               8.0000000000000000

item1               1.0000000000000000
item1               2.0000000000000000
item1               3.0000000000000000
item1               4.0000000000000000
item1               5.0000000000000000
item1               6.0000000000000000
item1               7.0000000000000000
item1               8.0000000000000000

and in anyone that supports f2003 …

Fortran 2023 contains several extensions to Fortran 2018; these are listed below.
• Source form:
The maximum length of a line in free form source has been increased. The maximum length of a statement
has been increased. The limit on the number of continuation lines has been removed.

So you can make the lines really long and put a lot more values on a line, and the limit on the number of continuation lines should be gone; although I think the number of characters in the line would cause a limit to be imposed at some point anyway.

But if the data can be declared by an expression in an implied loop a declaration like used for DB2 above can be very compact, and if the data repeats a repeat count in a DATA statement is even more succinct, and for constants array syntax (ie. R=0 where R is any size array works) is particularly simple.

1 Like

@davidpfister ,

I am dabbling with Fortran after a long, long time, actually I was pointed to your thread by a colleague at work who has to support one of a few remaining codebases in Fortran and who too was looking into compile-time computations and who reached out to me after noticing some old posts of mine (e.g., this). This colleague is adding some capabilities to the Fortran codebase in order to help it get consumed in cloud service requests, meaning concurrent execution.

Here’s the code example I suggested to this colleague who requested I also post here: the gist is a) use “named constant” facilities in Fortran as much as possible for “compile-time” data / database, etc. and b) avoid DATA statements, if possible, for you will find it’s not strictly compile-time computation and you are in effect applying the “static” (implied SAVE in Fortran parlance) attribute to the object that can prove pernicious in concurrent / parallel computing.

module kinds_m
   use ieee_arithmetic, only : ieee_selected_real_kind
   integer, parameter :: sp = ieee_selected_real_kind( p=6 )
   integer, parameter :: rp = sp
end module
 
module item_m
   use kinds_m, only : rp
   integer, parameter :: LENNAME = 8
   type :: item_t
      character(len=LENNAME) :: item_name
      real(kind=rp) :: val = 0.0_rp
   end type 
end module

program p

   use kinds_m, only : rp
   use item_m, only : item_t

   ! Compile time "database"
   integer, parameter :: n = 10000
   type(item_t), parameter :: db(*) =  &
      [( item_t( item_name="item1", val=real(i, kind=rp)), integer :: i = 1, n )]

   print *, "item ", "1", ": ", db(1)
   print *, "item ", "2", ": ", db(2)
   print *, ".. "
   print *, "item ", n, ": ", db(n)

end program 

You can execute this with a modern Fortran compiler of your choice to get response as follows:

C:\Temp>ifx /free /standard-semantics p.f
Intel(R) Fortran Compiler for applications running on Intel(R) 64, Version 2023.0.0 Build 20221201
Copyright (C) 1985-2022 Intel Corporation. All rights reserved.

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

-out:p.exe
-subsystem:console
p.obj

C:\Temp>p.exe
 item 1: item1    1.000000
 item 2: item1    2.000000
 ..
 item  10000 : item1    10000.00

C:\Temp>

Add CONSTEXPR procedures in Fortran · Issue #214 · j3-fortran/fortran_proposals
Perhaps you will review this suggestion of mine to Fortran language workers re: CONSTEXPR attribute on suitable functions in Fortran but it is languishing. Such a facility may help you - some 40 to 50 years from now - with better setting up of “compile-time” database viz. not having to name each item as item1 :winking_face_with_tongue: (.. item(‘item1’, 1.0_rp), .. item(‘item1’, 2.0_rp))

1 Like
program stuff
integer,parameter          :: rp=kind(1.0d0)
integer,parameter          :: m=999
type item
   character(len=20)       :: desc
   real(kind=rp)           :: value
end type item
type(item) :: db2(m)=[( &
& item('item'//char(mod(i/100,10)+48)//char(mod(i/10,10)+48)//char(mod(i/1,10)+48), i*1.0_rp), &
& i=1,m ) ]
   write(*,'(2(g0))')db2
end program stuff

You can make the IDs unique strings using CHAR():

item001             1.0000000000000000
item002             2.0000000000000000
item003             3.0000000000000000
            :
            :
item997             997.00000000000000
item998             998.00000000000000
item999             999.00000000000000

Fortran 2023 does away with the continuation limit entirely. A single statement cannot contain more than 1,000,000 characters. In free-form, a line may contain up to 10,000 characters. As compilers update this should become more widely available.

1 Like

I think this should use the achar() intrinsic instead. In cases where it matters, you want the native translation of the ascii characters here, not the raw native characters.

Or, another approach might be something like

char(mod(i/100,10)+ichar('0'))

This assumes only that the digits are contiguous within the native character set.

Otherwise, this is a nice trick to generate multidigit integers in strings. :slight_smile:

Good to know. For the moment, I am stuck with ifort, and in the futur I’ll try to keep the backward compatibility as long as possible.

Thanks for the tip. I had no idea about the concurrency issues `data` could cause. This is anyway, only a temporary solution for me. I plan to migrate the db to a proper database, that’s why I developed the odbc wrapper in the first place.