No reserved keywords: Why?

Well, if you wanted to reserve the intrinsics (or rename them for that matter) you could do something like this; so you get the best of both worlds with Fortran

module M_intrinsics
implicit none
private
public :: sin, cos, tan
intrinsic sin, cos, tan
end module M_intrinsics
program reserve
use M_intrinsics
!integer :: sin
write(*,*)sin([0.0,1.0])
contains
!real function sin(x)
!   x=3.0
!end function 
end program reserve

I have some very long formulas where I like abbreviations, which this lets you do to …

use M_intrinsics, s=>sin, c=>cos, t=>tan

but it gets a little odd with overloading last I tried it (I overload REAL and INT so they can take character representations of numbers, for example).

1 Like

having a function and intrinsic type makes things a little confusing already, but I do not think it is surprising the name just refers to the array. It should. That is why, especially in F77 some places
required INTRINSIC and EXTERNAL statements for all procedures used (plus it made the code more self-documented). Now when you can define interfaces EXTERNAL in particular can cause problems
when “modernizing” code. Use a procedure in a module and also declare the procedure with an EXTERNAL and with compilers I have used the module procedure is ignored, as if EXTERNAL says “undo interface”; last I tried it. It confused me when I was changing some old code to use modules that contained EXTERNAL statements. First, “real(1)=real(2)” should not act as if the intrinsic real even exists:

program real_name
!intrinsic real ! this would "reserve" the name
type(real) :: real(3) !function REAL() is now gone
real=[10.0,20.0,30.0]
   write(*,*)'A:',real
   real(1) = real(2) ! "real" is just like any array
   !real(1) = real(2,kind=4) ! REAL() is more obviously gone
   write(*,*)'B:',real
   ! this would let you get back to the intrinsic
   associate (real_var=>real)
    block
    intrinsic real
       real_var(2) = real(3)
    endblock
   end associate
 write(*,*)'C:',real
end program real_name

Then, when I was grabbing old procedures and placing them into modules I could not figure
out why I was getting “unsatified external” when I loaded the code, till I realized that in the rather
extensive documentation at the beginning of the routines the list of external statements was not
comments, but actual EXTERNAL statements …

 module A
contains
subroutine mysub
   write(*,*)'mysub'
end subroutine mysub
subroutine mysub2
external mysub
   call mysub
end subroutine mysub2
end module A
program confused
use A
   call mysub2()
end program confused