Type mismatch in literal constant/constructor for derived type - allowed?

I ran into a peculiarity with a literal constant (structure constructor) for a derived type. I checked the program below with gfortran and Intel Fortran oneAPI and both are happy to build it:

program chk_type_define
    implicit none

    type :: params
        real :: x
        real :: y
    end type params

    type(params) :: p

    p = params( 1, 2.0 )

    ! Also accepted:
    p = params( 10d0, 2 )

    ! Also accepted:
    p = params( (-1.0,3.0), 2 )


    write(*,*) p
end program chk_type_define

My question is: is this really allowed or is this an oversight in both compilers? Since Fortran is usually quite strict when it comes to types and kinds, I would expect the compilers to protest against this mixture. Of course, this literal only looks like a function invocation, but it does puzzle me that the ordinary TKR rules do not seem to apply here. (Well, the “R” part does)

This is perhaps surprising but follows the rules of the language.
Following document J3/24-007, structure constructor rules include:

7.5.10 p2 “For a nonpointer component, the declared type and type parameters of the component and expr shall conform in the same way as for a variable and expr in an intrinsic assignment statement (10.2.1.2).”

10.2.1.2 p1 “if the variable is not polymorphic and expr is not a boz-literal-constant, the declared types of the variable and expr shall conform as specified in Table 10.8,”

Table 10.8

Type of the variable Type of expr
integer integer, real, complex
real integer, real, complex
complex integer, real, complex

10.2.1.3 p 8 “For an intrinsic assignment statement where the variable is of numeric type, the expr can have a different numeric type or kind type parameter, in which case the value of expr is converted to the type and kind type parameter of the variable according to the rules of Table 10.9.”

Table 10.9

Type of the variable Value assigned
integer INT (expr, KIND = KIND (variable))
real REAL (expr, KIND = KIND (variable))
complex CMPLX (expr, KIND = KIND (variable))

REAL intrinsic:
16.9.172 p5 Result Value, Case (ii): If A is of type complex, the result is equal to a processor-dependent approximation to the real part of A.


If you declare a REAL px, does your compiler warn about px=(-1.0,2.0) or px=3?

Intel Fortran oneAPI silently converts a complex number, whereas gfortran warns about it, if you ask for all warnings.

But thanks for the explanation - basically, a structure constructor is considered a series of expressions. Hence the implicit conversions.

gfortran -Wall for version 14.0.1 20240121 does say

xassign_type.f90:17:16:

   17 |     p = params( (-1.0,3.0), 2 )
      |                1
Warning: Non-zero imaginary part discarded in conversion from 'COMPLEX(4)' to 'REAL(4)' at (1) [-Wconversion]

I would say that fortran is quite permissive with implicit conversions within expressions and with assignments. A derived type constructor takes on the assignment semantics, so it is permissive for this reason. For example, the implicit conversion

   p = params( 1, 2.0 )

is the same as the explicit

    p = params( real(1), 2.0 )

which a programmer could write in order to make it clear to another human reader of the code what is occurring. Both statements should compile to exactly the same instructions, there is no new intrinsic conversion that is being done, it is just a question of whether that conversion is implict or explicit.

Just curious. Do any of the commonly used compilers have option(s) to turn off implicit conversion. I’ve always thought it would be nice if a compiler could use the type and/or result of a function to satisfy TKR rules but Fortran’s long history of implicit conversion apparently prevents that.

I showed that gfortran gives a -Wconversion warning for the OP’s code. Any type of gfortran warning can be turned into an error. In this case, gfortran -Werror=conversion causes the compilation to fail and also causes

implicit none
real :: x
x = (-1.0, 2.0)
print*,x
end

to not compile, with the message

xassign.f90:3:4:

    3 | x = (-1.0, 2.0)
      |    1
Error: Non-zero imaginary part discarded in conversion from 'COMPLEX(4)' to 'REAL(4)' at (1) [-Werror=conversion]
f951.exe: some warnings being treated as errors

What is supposed to happen when a procedure shadows the structure constructor?

module foo

implicit none
private

public :: params

type :: params
    real :: x
    real :: y
end type params

interface params
    module procedure default_params
end interface

contains

    function default_params(x, y) result(this)
        real, intent(in) :: x, y
        type(params) :: this
        print *, "Not the structure constructor"
        this%x = x
        this%y = y * 2
    end function

end module

program chk_type_define
    use foo
    implicit none

    type(params) :: p

    p = params( 1, 2.0 )

    ! Also accepted:
    p = params( 10.0d0, 2 )

    ! Also accepted:
    p = params( (-1.0,3.0), 2 )

    write(*,*) p
end program chk_type_define

If the compiler can find a function that matches the actual arguments then it calls it, otherwise the default constructor is used.

Thanks @PierU, I understand what’s happening now, in none of the cases two real literals are passed, hence it uses the structure constructor that allows the conversions. I find it surprising, and also kind of dangerous this cannot be turned off. Making the components private could prevent such unwanted usage, but it also makes I/O unavailable by default, and forces you to use getter and setter functions, which are not worth the hassle for small types like this.

C++ also allows conversions during class construction:

#include <iostream>

struct point {
    float x, y;
};

int main() {
    point p{1.0, 2};      // (double, int)
    std::cout << p.x << ", " << p.y << '\n';
    return 0;
}

There are some methods to turn such implicit conversions off. For example with C++20 type traits,

#include <type_traits>

struct point {
    template<typename T> requires std::same_as<float, T>
    point(T x_, T y_) : x(x_), y(y_) {}

    float x, y;
};

you can get the compiler to enforce the types:

$ g++-13 -std=c++20 type_example.cpp 
type_example.cpp: In function ‘int main()’:
type_example.cpp:12:19: error: no matching function for call to ‘point::point(<brace-enclosed initializer list>)’
   12 |     point p{1.0, 2};
      |                   ^
type_example.cpp:6:5: note: candidate: ‘template<class T>  requires  same_as<float, T> point::point(T, T)’
    6 |     point(T x_, T y_) : x(x_), y(y_) {}
      |     ^~~~~
type_example.cpp:6:5: note:   template argument deduction/substitution failed:

To fix the error, the instance must be initialized as p{1.0f, 2.0f} (notice the float literal, since in C++ floating point literals are type double by default).

I sometimes like to use the compiler options that warn about implicit conversions when developing codes. If those compiler options were in higher demand, then there might be a good case to add that functionality into the standard somehow. But for everyone who wants to turn off the implicit conversions and to require only explicit ones, it seems that there are as many, or more, programmers wanting to extend the implicit conversions to cover even more cases. A common request here is to automatically convert real literal constants to a higher precision kind, as if appending the _wp characters is just too much effort for a programmer to bear. Regarding implicit conversions in general, I sometimes use them but add extra parentheses.

   x = (i)

rather than the full-blown explicit conversion syntax x=real(i,kind(x)). I do the same for mixed-type expressions that have implicit type conversions. This still draws attention of a human reader to the conversion, but it is not so verbose as to detract from the form of the expression.

One other comment regarding the original issue of derived type constructors, it is also allowed to use the component name.

p = params( x=1, y=2.0 )
p = params( x=(1), y=2.0 )
p = params( x=real(1), y=2.0 )
p = params( x=real(1,wp), y=2.0 )

Just the presence of the component name helps to call attention to the type conversion that is taking place.

1 Like

I was confused as I interpreted the constructor invocation as the invocation of a regular function. Instead it acts a series of expressions. And within an expression automatic conversions take place whenever possible.

1 Like