Automatic object of parameterized derived type

I discovered that gfortran gives a compilation error while trying to use an automatic object of a parameterized derived type. For example, trying to compile

module vector                                                                                                                           
  type :: vec(dimen)                                                                                                                    
    integer,len :: dimen                                                                                                                
    real        :: e(dimen)                                                                                                             
  end type vec                                                                                                                          
                                                                                                                                        
contains                                                                                                                                
  function double(a)                                                                                                                  
    type(vec(*)),intent(in) :: a                                                                                                        
    type(vec(a%dimen))      :: double                                                                                                   
                                                                                                                                        
    double%e = 2.*a%e                                                                                                                   
  end function double                                                                                                                   
end module vector

results into the following error:
Error: The AUTOMATIC object ‘double’ at (1) must not have the SAVE attribute or be a variable declared in the main program, a module or a submodule(F08/C513)
I cannot make sense out of it. Where is the save attribute? Also, ifort compiles without complain. This convinced me that this must be a compiler bug. I tried f18, just as a check, before going for bugzilla. And lo! it spits the same error verbatim. Now, I’m confused. Am I missing something in the standard? How come two different compilers are giving exactly same error message?

2 Likes

Parametrized derived type support is a weak point in GFortran. You are encountering it in f18 as well since it is currently just a parser, see here. It will unparse the source code and invoke another compiler, like GFortran, therefore you are observing the same error message in f18.

I checked the above code with Intel Fortran and NAG, which both compile it without problems. Sadly, if you want to use PDTs, you can’t do it in GFortran right now.

2 Likes

I went ahead and deleted a few posts that were not constructive and off topic. Please keep the discussion respectful and on topic, everybody.

3 Likes

I checked the Cray/HPE compiler - also compiled the module with no message. As an aside, the “must not have the SAVE attribute or be a variable declare in the main program” does not make much sense since a variable declared in the main program automatically has the SAVE attribute. Text from the standard:

“A variable, common block, or procedure pointer declared in the scoping unit of a main program, module, or submodule implicitly has the SAVE attribute, …”

"An automatic data object is a nondummy data object with a type parameter or array bound that depends on the value of a specification-expr that is not a constant expression.

C814 An automatic data object shall not have the SAVE attribute."

2 Likes

With gfortran-10.2 + Mac, the following code (modified slightly such that the result variable is explicitly declared as in test2()) seems to work:

module test_m
    implicit none

    type :: vec_t(dim)
        integer, len :: dim
        real         :: el( dim )
    end type
contains

!function test1(a)
!    type(vec_t(*)), intent(in) :: a
!    type(vec_t(a%dim))         :: test1
!    test1% el(:) = 2.0 * a% el(:)
!end

function test2(a) result(res)
    type(vec_t(*)), intent(in) :: a
    type(vec_t(a%dim))         :: res

    res% el(:) = 2.0 * a% el(:)
end

end module

program main
    use test_m
    implicit none
    type(vec_t(3)) :: v, w

    v% el(:) = [1.0, 2.0, 3.0]
    print *, "v = ", v
    print *, "w = ", w
    print *
    print *, "test2(v) (dim, el(:)) = ", test2( v )

    w = v
    print *, "w = ", w
end

$ gfortran-10 test.f90 && ./a.out

 v =  3   1.00000000   2.00000000      3.00000000    
 w =  3   0.00000000  -1.08420217E-19  0.00000000 

 test2(v) (dim, el(:)) =  3   2.00000000   4.00000000  6.00000000    
 w =  3   1.00000000   2.00000000      3.00000000  

If I uncomment test1(), I get the same error:

Error: The AUTOMATIC object 'test1' at (1) must not
have the SAVE attribute or be a variable declared
in the main program, a module or a submodule(F08/C513)

So I guess the function name (test1) might be possibly interpreted as some global variable internally, resulting in some interference with the check that “saved variables shall not be used as dummy/automatic variables”.

By the way, if I attach the default value to the component el

    real :: el( dim ) = 0

the compilation fails like

internal compiler error: in gfc_conv_expr_descriptor,
at fortran/trans-array.c:7216

but first of all, I am not sure whether my code above is okay (valid) to have the
default value in PDT (?)…

4 Likes

This is of great help!

This works for my configuration (fedora+gfortran 11.1) as well.
I will add this information to the bug report.

There was already a debate on stackexchange on whether this is standard compliant or not:

Somebody even messaged the standards committee. There is no report of their reply and the discussion was inconclusive.

I hope somebody on this forum will enlighten us.

For whatever it’s worth, I find the above component initialization to be non-conformant to the Fortran standard. The shown initialization violates a constraint and thus the compiler is required to issue a diagnostic. That gfortran does not do so is another bug in that compiler.

C762 (R737) If component-initialization appears, every type parameter and
array bound of the component shall be a colon or constant expression.

C:\Temp>type m.f90
module m
type :: t(n)
integer, len :: n
real :: x(n) = 0.0
end type
end module

C:\Temp>gfortran -c -Wall m.f90

C:\Temp>

1 Like

Despite the conflict in standard (see comments below top rated answer on the page I linked in my previous answer), ifort indeed gives a compilation error.

I have found yet another bug in PDT. It involves using a PDT object as a component of another class. I have also seen the flurry of bugs you had posted on the mailing list. I saddens me that despite all the hard work that has gone into making PDT available in gfortran, it is still on the verge of being unusable.

Aside, I have not seen many codes using PDT. Would like to know how common it is among practitioners. Is it the state of compilers that is holding them back, or the feature itself has limited utility.

I had earlier posted my views here listing the benefits we have noticed with PDTs:

Parameterized derived types (PDTs) are significantly more useful than so many other facilities introduced in the language starting Fortran 90. With the somewhat more complicated length-type parameter, it is a feature of convenience that eases the tedium with derived type components with the ALLOCATABLE attribute.

However to make such convenience available to the practitioners of Fortran, the time and effort required of the standard bearers and particularly the compiler implementors with PDTs is somewhat higher than what they are used to with many other convenience features (like those listed under “Miscellaneous Enhancements” in Chapter 16 or Other … Enhancements under Chapter 20 in 7th edition of Modern Fortran Explained).

The extra effort and attention required with PDTs has led to consternation and dread with implementors because the impression with Fortran is what “sells” is only performance-oriented facilities and HPC stuff, PDTs do not fit such performance categories and then the added effort is viewed as not satisfying much of the informal and rudimentary “cost-benefit” analyses around this facility by implementors where the feedback of ordinary practitioners like yours truly on the “benefits” side of the column is effectively ignored. All that gets noticed is the “cost”.

This is among the reasons why PDTs lie dormant in gfortran since the Fall of 2017:
https://groups.google.com/g/comp.lang.fortran/c/NDE6JKTFbNU/m/dD8mOww6AQAJ

It takes enormous communication and campaigning effort, tremendous credentials and major institutional affiliations and innate drive to bring change and progress along with large $$ contracts to catch the attention. Those leading the advancement of C#, C++, Julia, Python, R, Swift all have this, Fortran not as much. Even very recently on this very forum and in standard committee meetings, there are instances where certain committee members nonchalantly state “no one” is asking for certain feature in a Fortran standard when one can point to threads after threads on comp.lang.fortran, Intel Fortran forum, StackOverflow, GitHub Fortran proposals site, WG5 Fortran’s own survey, and now this site where more than a few different practitioners of Fortran would have requested same or similar facilities. But these practitioners are not those signing the big hardware/software contracts with Intel, Cray, AMD, IBM, NAG, etc. so their “voices” are not easily heard. On the other hand, GNU GCC/gfortran front-end development with its use of particular C language idioms and architecture and previous FOSS workflow has failed to attract enough new volunteers, so certain aspects have languished in that system when it comes to Fortran. PDTs have suffered the brunt of all such non-technical issues.

On the positive side though, things are starting to improve of late with Fortran, one can only hope the landscape will be more green and promising in a few years.

2 Likes

NOTE 3 from the standard mentioned in that link is in error. The code snippet in that Note does not conform, I’ll follow up on that separately with the standards committee.

For a derived type with allocatable components, I have a subroutine to ALLOCATE it. There is not much tedium:

type :: date_frame
   character (len=1000)                  :: title = ""
   type(date_mdy)          , allocatable :: dates(:)  ! (nobs)
   character (len=len_sym) , allocatable :: sym(:)    ! (nvar)
   real(kind=dp)           , allocatable :: xx(:,:)   ! (nobs,nvar)
   logical                 , allocatable :: good(:,:) ! (nobs,nvar)
   character (len=len_name), allocatable :: names(:)  ! (nvar)
end type date_frame

subroutine alloc_date_frame(df,nobs,nvar,xinit,good_init)
! allocate a date_frame to have the specified number of observations and variables
type(date_frame), intent(out) :: df
integer         , intent(in)  :: nobs,nvar
real(kind=dp)   , intent(in), optional :: xinit
logical         , intent(in), optional :: good_init ! value to which df%good is initialized
allocate (df%dates(nobs),df%sym(nvar),df%xx(nobs,nvar),df%good(nobs,nvar))
if (present(xinit)) df%xx = xinit
if (present(good_init)) df%good = good_init
end subroutine alloc_date_frame

These are precisely the discussions that lead to the fundamental question, “For whom Fortran, for what!?”

Sure if I am looking out for myself for my practice of Fortran with only my limited view of a “frog in a well”, looking at my own “toy” programs, or as a one-person team developing solutions - even if mid-size - for use by one or a few other people, and with a certain number of objects coming into existence during run-time such that their sizes are individually manageable, sure my own tedium with having to author such “allocation” subroutines can be ignored, especially by others who strongly prefer to view Fortran narrowly for computing needs that require FORTRAN 77 plus implicit none and may be free-form source and C interoperability and perhaps coarrays.

But as I mentioned previously (point 1), there are computing needs where the calculations and simulations involve multiphysics architectures that are spread across many teams with many contributors working with innumerable number of objects in memory as part of countless classes (like derived types in Fortran) whose allocation sizes can be parameterized using a few quantities, similar to nobs and nvars above. This is precisely where the value of the length-type parameter comes in and where much tedium can be avoided.

Here is a tutorial on parameterized derived types: Parameterized derived types in Fortran - introduction, by Iain Barrass. I would be happy to see them more widely implemented.

1 Like

@FortranFan I had already seen your ‘previous’ answer before commenting. Though, being an FEM practitioner, I have some feel of what you mean, I would like to see some concrete example of PDT’s advantage over DT with allocatable components.

@Beliavsky Thanks for the link. But, the tutorial is just stating the obvious. It can, however, serve as a summary of syntax. I am more interested in the next blog promised by the author.

EDIT- Unfortunately, none of the famous style guides on Fortran, be it Markus, Clerman or Curcic, gives any significant focus to PDTs.

For me personally it has been the state of compilers (gfortran). I’ve experimented a few times, and sooner or later always bumped into ICE’s. Now that Intel Fortran compiler can be installed freely, the situation has changed and I might revisit PDT’s.

For the stdlib bitset type both William Clodius and I experimented with a PDT (see the comments: A, B), but ultimately dropped it because it did not work with gfortran. I’d be happy to revisit this in the future. A bitset using PDT would lead to a fixed-size bitset equivalent to the C++ templated std::bitset<> class.

Another application where I believe PDT’s would be extremely helpful are spatial search tress (ball trees, k-D trees). Using a PDT would allows callers to use code like:

real(dp), allocatable :: xyz(:,:)
type(kdtree(dp)) :: tree

allocate(xyz(3,10000000)) ! point coordinates

! ... initialize points ...

tree = kdtree(xyz)

Without PDT’s, specializations of the tree (child classes) are needed for each supported real type, or we need to keep track of the type internally, making the code bloated. Wrong usage like searching for a point given double precision, in a tree built from points in single precision have to be handled at runtime.

I like to think of the kind specifier equivalent to how C++ codes use templates to allow varying the precision, e.g. the nanoflann kd-tree library defines the following base class:

template <class Derived, typename Distance, class DatasetAdaptor, int DIM = -1,
          typename IndexType = size_t>
class KDTreeBaseClass {
\\ ...

The Distance typename is used to specify the type of coordinates in the tree (float, double, or even integers in this case), and the IndexType is the integer precision used to iterate over the points in three (meaning you can choose a large integer if you expect your tree to contain many points).

This pattern is used in practically all scientific C++ codes that offer some classes.

4 Likes

Yes kind parameters can reduce lots of boilerplate code. What about length parameters? It is PDTs with length type parameters which are judged against those with allocatable components.

I have always seen PDTs as watered down approach to templated classes. It turns out that one of the best advantage for numerics obtained from templates is lost due to restriction placed in Fortran. Blitz++ and many other C++ libraries use expression templates for generating extremely efficient numerical codes. There appears no way of doing so in Fortran.

2 Likes

The bitset example mentioned would use the length specifier. A second example in connection with the k-D trees or radial basis function interpolation would be to use the length specifier for the problem dimensionality

type(rbf_interpolant(dp,3)) :: rbf3d 
type(rbf_interpolant(dp,2)) :: rbf2d
 
real(dp) :: p(3), y3d, y2d

! ... initialize RBF interpolant ...

! evaluate RBF at Cartesian point p
y3d = rbf3d%eval(p)
y2d = rbf2d%eval(p) ! generate compiler error, size(p) /= 2

Concerning expression templates I am sure there are situations where they would be welcome in Fortran. The naive example on Wikipedia shows expression templates used for implementing delayed evaluation of a vector class, something that is best compared to the Fortran array syntax res = a + b + c which is available straight out of the box.

On the other hand C++ users are forced to pick between several libraries with slightly different API’s:

If you decide to rely to tightly on any of them, it can be very challenging down the road to switch to a different one. I recall reading about linear algebra codes using expression templates beating LAPACK for small matrix sizes. Ideally, we would see similar optimization performed by the Fortran compilers.

Interestingly, the POOMA home page (dating to 1999) contains a few paragraphs on Fortran:

In fact, the combination of C++ and POOMA provides so many of the features of Fortran 90 that one might well ask whether it wouldn’t better to just use the latter language.

The simple answer is that the abstraction facilities of C++ are much more powerful than those in Fortran. A more powerful answer is economics. While the various flavors of Fortran are still the lingua franca of scientific computing, Fortran’s user base is shrinking, particularly in comparison to C++. Networking, graphics, database access, and operating system interfaces are available to C++ programmers long before they’re available in Fortran (if they become available at all). What’s more, support tools such as debuggers and memory inspectors are primarily targeted at C++ developers, as are hundreds of books, journal articles, and web sites.

Until recently, Fortran has had two powerful arguments in its favor: legacy applications and performance. However, the importance of the former is diminishing as the invention of new algorithms force programmers to rewrite old codes, while the invention of techniques such as expression templates has made it possible for C++ programs to match, or exceed, the performance of highly optimized Fortran 77.

Quite interestingly, there are proposals for C++23 to include a standard set of linear algebra templates in the standard library, see the documents

What do we need from a linear algebra library?

A proposal to add linear algebra support to the C++ standard library

There are several other interesting proposals of relevance for scientific computing in the C++ community, including differentiable programming, BLAS interface, statistical functions, graph library and also special functions (already accepted).

3 Likes

Just consider the case above by @Beliavsky :

To repeat the obvious, with length-type parameters, not only does the “library” side not need to implement such “allocation” subroutines (which do become “boilerplate” if such a coding practice with ALLOCATABLEs gets extended to all such derived types), the “client” is not forced to invoke such procedures before they can even start to consume the derived type. The type-declaration itself [type(data_frame(nobs=xx,nvars=yy)) :: foo] defines the object in terms of the problem size, considerable brevity is achieved.

1 Like

In case the nobs and nvars arguments can only be inferred at run-time (e.g. a Fortran program fulfilling a request from a server), would the best practice initialization pattern be something like:

type(data_frame(nobs=:,nvars=:)), allocatable :: foo

call alloc_date_frame(foo,nobs,nvar,xinit,good_init)  ! or
foo = data_frame(nobs,nvar,xinit,good_init)

and the allocation of the right size is performed by the routine, or in a two-step process like

allocate( data_frame(nobs,nvar) :: foo)
call foo%init(xinit,good_init)

I can see the brevity when sizes are known, but for allocatable entities there appear to be some tradeoffs.

1 Like

Pardon my ignorance, is merging of loops/delayed evaluation available in Fortran for non-native arrays, when the binary operator is overloaded for a user defined type? If yes, then we have a clear edge over C++. If no, then we should look out for a mechanism to incorporate.

Interesting to note! Long ago, when C++11 was under preparation and was known as C++0x and I had not learned Fortran, I had a small communication with Stroustrup on whether he has specific plans for supporting numerics in the upcoming standard. He was quite positive about it. But, it later turned out that most in their committee were not considerate. There argument, I read somewhere, was that numerics people have a dedicated language: Fortran. Core C++ should be kept application agnostic. The trend, it appears, has buckled. But, I no longer feel attracted towards C++.