Is it possible to overwrite intrinsics?

Is it possible to overwrite intrinsics? For example

module mymod
  use iso_fortran_env, only: dp => real64
  implicit none
  
  interface operator(**)
    module procedure pow
  end interface
  
contains
  
  pure elemental function pow(a, b) result(res)
    real(dp), intent(in) :: a, b
    real(dp) :: res
    
    real(dp), parameter :: log10 = log(10.0_dp)
    
    if (a == 10.0_dp) then
      res = exp(log10*b)
    else
      res = exp(log(a)*b)
    endif

  end function

end module

This gives a compilation error:

    6 |     module procedure pow
      |                        1
Error: Operator interface at (1) conflicts with intrinsic interface

ifort gives a different error message

pow.f90(11): error #6748: The type/rank for the arguments of this specific function for a defined OPERATOR redefines intrinsic expression operations. [POW]
pure elemental function pow(a, b) result(res)
--------------------------^
compilation aborted for pow.f90 (code 1)

NVIDIA (PGI) fortran compiles without any errors. Given how far behind NVIDIA is as far as standard compliance, I wonder if this is a violation related to newer versions of the standard. I personally don’t see any reason why your code shouldn’t compile but I rarely try to overload intrinsic operators so it’s entirely possible this is illegal

1 Like

My instinct, confirmed by nagfor, is that no, it is not possible to override an intrinsic operator.

$ nagfor -c overload.f90 
NAG Fortran Compiler Release 7.1(Hanzomon) Build 7108
Error: overload.f90, line 24: Overload POW for OPERATOR(**) conflicts with intrinsic operation
Errors in declarations, no further processing for MYMOD
[NAG Fortran Compiler error termination, 1 error]

You can add specific procedures to the generic interface of the intrinsic operators, but they must not have conflicting interfaces with the intrinsic operators.

1 Like

Must be something unique about ** because if you
replace ** with // ifort and gfortran 11 both compile without error

1 Like

I think it makes sense for a compiler by default to not allow overwriting intrinsics. This will help catch mistakes. But it would be nice to have a flag that allows it for specific libraries.

@rwmsu I think // is allowed by gfortran because the the intrinsic only applies to characters, and there is no intrinsic for reals.

Well here is something weird, if you change the b argument in your function to
integer it compiles with ifort but not with gfortran-11. This problem illustrates one
of my biggest frustrations with the current crop of compilers. Namely, inconsistent
detection and enforcement of the standards among the various vendors/developers.

1 Like

@nicholaswogan , perhaps the way you may want to look at it is the standard allows you to extend intrinsic operators so they can be used with derived types but the standard does not allow you to override the operations on intrinsic data types. The example below shows what the standard permits with the former:

module fp_m
! module for a derived type to model a floating-point type
   type :: fp_t
      real :: val = 0.0
   end type
   generic :: operator(**) => pow_fp_t
contains
   function pow_fp_t( lhs, rhs ) result(r)
      type(fp_t), intent(in) :: lhs
      type(fp_t), intent(in) :: rhs
      type(fp_t) :: r
      r%val = lhs%val ** rhs%val
   end function 
end module
   use fp_m
   real :: a, b
   type(fp_t) :: x, y
   a = 2.0 ; b = 2.0
   print *, a**b
   x%val = a ; y%val = b
   print *, x**y
end
C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.6.0 Build 20220226_000000
Copyright (C) 1985-2022 Intel Corporation.  All rights reserved.

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

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

C:\temp>p.exe
 4.000000
 4.000000

Ok ya I understand this functionality.

The benefit of overwriting an intrinsic would allow you to write specialized implementations of an intrinsic that are more efficient in certain scenarios. The code i gave in the original post is an example. This will be faster than intrinsic **, if a code contains a lot of 10.0**x. So you could easily speed up a code by just importing your faster intrinsic into the relevant subroutine (use fast_ten_pow_mod, only: operator(**))

Ya, I don’t have time to help with Gfortran either. I might try to set aside time in the future to help with LFortran. The LFortran codebase is easier to understand.

If there aren’t enough developers to keep gfrotran working, would it make sense to deprecate gfortran and focus support on flang/LFortran

@kargl, maybe its time you learned that not everything anyone says here is a slight at you or gfortran. My post was basically “a plague on all your houses”. In my opinion, ALL current compilers fail in one area or another, be it detecting syntax errors or failing with ICEs on standard conforming code. In this instance, I think gfortran is right. nvfortran and ifort are not.

Note that in one sense Fortran has always allowed overwriting intrinsics, as it does not reserve names.
Extending the intrinsic is restricted in that you can only add a procedure that provides a unique interface;
but as long as you do not explicitly specify a name as INTRINSIC you can call your routine instead of the intrinsic. You can play games with providing an “override” module that you have a null version of and one that provides overrides if you want; and you can create routines of your own (with some overhead costs) that can call either your code or the intrinsic (or a combination of the two). WIthout explicit interfaces it is easy (ie. it was easy with F77); but if you really want the interfaces there are ways to do it as mentioned, and other ways involving procedure pointers. Might not fit a textbook definition of overwriting a built-in function, but I and others have done something close to it many times.

If you are trying to do it with existing code without changing it and the code contains INTRINSIC and EXTERNAL declarations for all the functions you might get stuck; and if you insist on requiring explicit interfaces it gets more complicated but is still do-able. The choices hinge mostly on whether you want to be able to change a single executable’s behavior at run time, or are willing to recompile, how much you hate preprocessors, and what kind of overhead is tolerable. Think F77 and it is relatively trivial.

PS: Somewhat obvious, but I forgot to mention using an alternate library on load as well, as most intrinics are procedures (versus macros, …) but there are a few gotchas there, especially for high optimization levels.

PS: I feel indebted to all the G95 and gfortran developers, and am convinced they saved Fortran in many respects. I think an interesting question to ask as well is “why people do not get involved”, such as the learning curve (a code history utility, the bugzilla interface, …) and those mentioned; would be why contributors leave being contributors. Outside of personal reasons, is there something that can be changed to making joining (or staying on) the gfortran development team better? Bounties, some change in the contribution process, …? That kind of information might be valuable for any project, not just gfortran ( fpm, compilers, web site maintenance, …).

1 Like

Imo the biggest factor is how easy it is to contribute. A few things that have worked well for Julia’s codebase. For reference, we have had 40 users contribute 100 or more lines in the past year. Not all of these are possibly for gfortran, but some are.

  1. Have docs that link to implementations. The more users see the code, the more they can improve it.
  2. Have language features that make it easy to see what the compiler is doing. (eg @code_typed, @code_llvm, @code_native)
  3. Write as little as possible in other languages. If users wanted to use C++, they would be.
  4. Have a solid CI setup. Automatic tests running on every PR makes it way easier to be confident that changes are correct.
  5. Host on GitHub. It allows for users to make simple changes without having to know git which makes first contributions much easier.
  6. Put in more time than necessary for new users. You might have to spend 5x longer to guide a new user on how to make a simple PR than it would take you to do it yourself, but if 1/10 keep contributing, it will pay itself back quickly.
4 Likes

This question was asked at Overload Fortran intrinsic operator on intrinsic types? - Stack Overflow, where a “no” answer was justified by quoting the standard:

15.4.3.4.2
Defined operations 1 If OPERATOR is specified in a generic specification, all of the procedures specified in the generic interface shall be functions that may be referenced as defined operations (10.1.6, 15.5). In the case of functions of two arguments, infix binary operator notation is implied. In the case of functions of one argument, prefix operator notation is implied. OPERATOR shall not be specified for functions with no arguments or for functions with more than two arguments. The dummy arguments shall be nonoptional dummy data objects and shall have the INTENT (IN) or VALUE attribute. The function result shall not have assumed character length. If the operator is an intrinsic-operator (R608), the number of dummy arguments shall be consistent with the intrinsic uses of that operator, and the types, kind type parameters, or ranks of the dummy arguments shall differ from those required for the intrinsic operation (10.1.5).

1 Like

In F77, EXTERNAL sin declaration meant that the user is providing his/her own sin implementation. Is it still so in modern Fortran?

Yes, in principle though technically in modern Fortran, a practitioner will be advised to

  1. furnish an explicit interface instead of using EXTERNAL, and
  2. employ the INTRINSIC attribute/statement to indicate explicitly a reference to an intrinsic procedure

With other readers in mind, an example will be as follows:

   real :: sinx
   sinx = sin(0.5)
   print *, "sin(0.5) = ", sinx
   block
      intrinsic :: sin
      print *, "Using intrinsic implementation:"
      print *, "sin(0.5) = ", sin(0.5)
   end block
contains
   impure elemental function sin(x) result(r)
      real, intent(in) :: x
      real :: r
      real, parameter :: PI = 3.1415926535
      real, parameter :: PI2 = PI*PI
      print *, "Using Bhaskara approximation:"
      r = 16*x*(PI-x)/(5*PI2-4*x*(PI-x))
   end function
end 
C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.5.0 Build 20211109_000000
Copyright (C) 1985-2021 Intel Corporation.  All rights reserved.

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

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

C:\temp>p.exe
 Using Bhaskara approximation:
 sin(0.5) =  0.4795828
 Using intrinsic implementation:
 sin(0.5) =  0.4794255
1 Like