Compilers differ in operator precedence

A recent post about redundant parentheses reminded me of a curious observation:

I am working on code that has overloaded the concat operator // to convert numbers into strings. It works fine with gfortran but ifort has a problem with this:

str = "foo" // i + j // "bar"

According to the Fortran Standard + has a higher precedence than //. And even if you consider // to be an extension when using it with something other than characters, it should even have the lowest precedence.

Using parentheses solves the issue but I think they should be optional.

Can you post a complete example? This seems a compiler bug to me.

I checked with a minimal example and could not reproduce. Will have a look what differs in the big code.

This minimal working example works with gfortran but not with ifort:

program concat_plus
    ! check if program compiles with + having higher precedence than //

    implicit none

    interface operator(//)
        procedure :: concat_str_int, concat_int_str
    end interface operator(//)

    write(*,*) "foo1234bar"
    write(*,*) "foo" // "1234" // "bar"
    write(*,*) "foo" // 1234
    write(*,*) 1234 // "bar"
    write(*,*) "foo" // 1234 // "bar"
    write(*,*) "foo" // 1200 + 0034
    write(*,*) 1200 + 0034 // "foo"
    write(*,*) "foo" // 1200 + 0034 // "bar"

    contains

    ! not a correct implementation
    function concat_int_str(int, str) result(res)
        integer, intent(in) :: int
        character(*), intent(in) :: str
        character(4+len(str)) :: res
        res = "1234" // str
    end function concat_int_str

    ! not a correct implementation
    function concat_str_int(str, int) result(res)
        character(*), intent(in) :: str
        integer, intent(in) :: int
        character(len(str)+4) :: res
        res = str // "1234"
    end function concat_str_int

end program concat_plus

Error:

$ ifort concat_plus.f90 -o concat.i
concat_plus.f90(14): error #6355: This binary operation is invalid for this data type.
    write(*,*) "foo" // 1200 + 0034
---------------------^
concat_plus.f90(14): error #6549: An arithmetic or LOGICAL type is required in this context.
    write(*,*) "foo" // 1200 + 0034
-----------------------------^
concat_plus.f90(16): error #6355: This binary operation is invalid for this data type.
    write(*,*) "foo" // 1200 + 0034 // "bar"
---------------------^
concat_plus.f90(16): error #6549: An arithmetic or LOGICAL type is required in this context.
    write(*,*) "foo" // 1200 + 0034 // "bar"
-----------------------------^
compilation aborted for concat_plus.f90 (code 1)

1 Like

This definitely looks like a compiler bug - user-defined binary operations have the lowest priority. If you rename it to .cat. or the like it is accepted.

1 Like

Does overloading // for non-character types count as // or a user-defined binary operation in terms of the Standard’s precedence table (which specifically mentions characters)?

Oh, that is a good one! I overlooked that possibility. No, I do not think an overloaded standard operation counts as that. The precedence should not be affected. Otherwise it will be very difficult to get it all right.

1 Like

@Sideboard ,

The term per the standard is defined operation, specifically a binary defined operation.

Regardless with your specific example, the + operator has higher precedence per the standard than the concatenation operation which Intel appears to ignore.

Hence you may want to inquire with Intel Support e.g., at their forum and get their feedback.


Edits following the comments by @sblionel:

  • I incorrectly stated the standard labels what it calls a binary defined operation as defined-binary-op. Per the standard, “A binary defined operation is an operation that has the form x1 defined-binary-op x2 or x1 intrinsic-operator x2 and that is defined by a function and a generic interface.”
  • I then incorrectly connected the rules in the standard toward precedence with defined-binary-op with those of the intrinsic-operator for concatenation.

Thanks for the explanation. Even if it counted as the intrinsic // operator, the precedence would be lower than +.

I will ask Intel about the case.

Out of curiosity I tried it with .true. .and. .true., now both gfortran and ifort complain. And it looks like gfortran counts this as the intrinsic //.

program concat_and
    ! check if program compiles with .and. having higher precedence than //

    implicit none

    interface operator(//)
        procedure :: concat_str_lval, concat_lval_str
    end interface operator(//)

    write(*,*) "fooTbar"
    write(*,*) "foo" // "T" // "bar"
    write(*,*) "foo" // .true.
    write(*,*) .true. // "bar"
    write(*,*) "foo" // .true. // "bar"
    write(*,*) "foo" // .true. .and. .true.
    write(*,*) .true. .and. .true. // "foo"
    write(*,*) "foo" // .true. .and. .true. // "bar"

    contains

    ! not a correct implementation
    function concat_lval_str(lval, str) result(res)
        logical, intent(in) :: lval
        character(*), intent(in) :: str
        character(1+len(str)) :: res
        res = "T" // str
    end function concat_lval_str

    ! not a correct implementation
    function concat_str_lval(str, lval) result(res)
        character(*), intent(in) :: str
        logical, intent(in) :: lval
        character(len(str)+1) :: res
        res = str // "T"
    end function concat_str_lval

end program concat_and
$ gfortran concat_and.f90 -o concat_and.g
concat_and.f90:15:36:

     write(*,*) "foo" // .true. .and. .true.
                                    1
Error: Operands of logical operator ‘.and.’ at (1) are CHARACTER(1)/LOGICAL(4)
concat_and.f90:16:27:

     write(*,*) .true. .and. .true. // "foo"
                           1
Error: Operands of logical operator ‘.and.’ at (1) are LOGICAL(4)/CHARACTER(1)
concat_and.f90:17:36:

     write(*,*) "foo" // .true. .and. .true. // "bar"
                                    1
Error: Operands of logical operator ‘.and.’ at (1) are CHARACTER(1)/CHARACTER(1)
$ ifort concat_and.f90 -o concat_and.i   
concat_and.f90(15): error #6385: The highest data type rank permitted is INTEGER(KIND=8).
    write(*,*) "foo" // .true. .and. .true.
---------------------^
concat_and.f90(15): error #6355: This binary operation is invalid for this data type.
    write(*,*) "foo" // .true. .and. .true.
---------------------^
concat_and.f90(16): error #6385: The highest data type rank permitted is INTEGER(KIND=8).
    write(*,*) .true. .and. .true. // "foo"
-----------------------------------^
concat_and.f90(16): error #6355: This binary operation is invalid for this data type.
    write(*,*) .true. .and. .true. // "foo"
-----------------------------------^
concat_and.f90(17): error #6385: The highest data type rank permitted is INTEGER(KIND=8).
    write(*,*) "foo" // .true. .and. .true. // "bar"
---------------------^
concat_and.f90(17): error #6385: The highest data type rank permitted is INTEGER(KIND=8).
    write(*,*) "foo" // .true. .and. .true. // "bar"
--------------------------------------------^
concat_and.f90(17): error #6355: This binary operation is invalid for this data type.
    write(*,*) "foo" // .true. .and. .true. // "bar"
---------------------^
concat_and.f90(17): error #6355: This binary operation is invalid for this data type.
    write(*,*) "foo" // .true. .and. .true. // "bar"
--------------------------------------------^
compilation aborted for concat_and.f90 (code 1)

I don’t agree with this at all.

R1023 defined-binary-op is . letter [ letter ] … .

There is no way that // can be interpreted as a defined-binary-op. These are syntax rules, and // is its own syntax term that appears in:

R1010 level-3-expr is [ level-3-expr concat-op ] level-2-expr
R1011 concat-op is //

That you extended the intrinsic with your own generic procedure does not magically make the intrinsic operator a defined-binary-op. Therefore, its precedence is unchanged.

I talk about operator precedence in Doctor Fortran in “Order! Order!” - Doctor Fortran (stevelionel.com)

2 Likes

Yes I agree. Edits have been made to my earlier comment.

@Sideboard , see the comments by @sblionel whereby the precedence of a defined operation is that of its operator. I have corrected my earlier post.