Resolving name conflicts of input variables with Fortran instrinsics

I am writing this Fortran to C interface which is auto generated from a script and I stumbled upon a very annoying limitation where a variable from the argument list shares the same name as a Fortran intrinsic (size) thus causing all sorts of problems.

subroutine foo(dimTags, size, ierr)
    use, intrinsic :: iso_c_binding
    integer(c_int), dimension(:), intent(in) :: dimTags
    real(c_double), intent(in) :: size
    integer(c_int), intent(out) :: ierr
    print*, size(dimTags, kind=c_size_t), size
end subroutine foo

Changing the variable names is not really an option, so my next best solution was to just create a local function for size to avoid the name conflict and wrap it around an interface for easy usage.

function fsize_sizet(o) result(sz)
    integer(c_int), dimension(:), intent(in) :: o
    integer(c_size_t) :: sz
    sz = size(o, kind=c_size_t)
end function fsize_sizet

That is perfectly fine, but my question is, is there a simpler, hopefully more elegant way of doing this?


PS I recall seeing a post on this Discourse about how it would be nice to allow for renaming (=>) of the Fortran intrinsics, but AFAIK that is not a thing yet.

I don’t think I did a very good job simplifying my problem to a MWE. I will attach a more accurate snippet of the code at the end, which led me to believe it’s naming conflict.

With regards to the MWE I originally posted, renaming the variable size to bar seems to work okay for me, and compiles/runs with no issues. Did I misunderstand your comment?

subroutine foo2(dimTags, bar, ierr)
    use, intrinsic :: iso_c_binding
    integer, dimension(:), intent(in) :: dimTags
    real(c_double), intent(in) :: bar
    integer(c_int), intent(out) :: ierr
    print*, size(dimTags, kind=c_size_t), bar
end subroutine foo2

More accurate snippet

subroutine gmshModelMeshSetSize(dimTags, size, ierr)
    integer(c_int), dimension(:), intent(in) :: dimTags
    real(c_double), intent(in) :: size
    integer(c_int), intent(out) :: ierr
    ! Local variables
    integer(c_int), dimension(size(dimTags)) :: api_dimTags_
    integer(c_size_t) :: api_dimTags_n_
end subroutine gmshModelMeshSetSize

which reports the following errors with gfortran 13.0.0 20220627

test.f90:29:34: Error: Expression at (1) must be of INTEGER type, found REAL
test.f90:29:34: Error: Expression at (1) must be of INTEGER type, found REAL
test.f90:24:49: Error: PROCEDURE attribute conflicts with INTENT attribute in ‘size’ at (1)

I suspect you are right, the first reference to size is what is being picked up, which is a real, but would that not be classified as a naming conflict?

Is this possibly another option…?

module test_m
    intrinsic :: size
end

program main
    use test_m, only: size_fn => size
    implicit none
    integer :: arr( 3 ), size

    size = 777
    print *, size_fn( arr ), size
end
3 Likes

This actually works, although I get a warning (-Wsurprising)

Warning: Type specified for intrinsic function ‘size’ at (1) is ignored [-Wsurprising]

Any idea if this has any consequences (or what it means)?

@gnikit,

It’s unclear what you are looking for here. But if such code can be refactored to help conform and assist the processor by providing some scope to control the conflicting definitions i.e., the dummy scalar argument in this case which is named size versus the intrinsic function with the same name, you may have some luck. Try this out to see what it might inform you:

subroutine foo(dimTags, size, ierr)
    use, intrinsic :: iso_c_binding
    integer(c_int), dimension(:), intent(in) :: dimTags
    real(c_double), intent(in) :: size
    integer(c_int), intent(out) :: ierr
    block
       intrinsic :: size
       print*, size(dimTags, kind=c_size_t)
    end block
    print *, size
end subroutine foo
1 Like

I am looking for an alternative way to resolve the name conflict of the intrinsic size() and the input argument size. The only real restrictions as I mentioned are:

  1. I can’t modify the variable name size
  2. Both the intrinsic and the variable need to be reachable in the same scope, as shown in the MWEs

Other than that it’s a pretty open-ended question, which is why I am looking for alternatives in the first place.

Thanks for the suggestion, but because of point 2. using a block would not work. @septc 's answer seems to do the trick with the exception of the warning, which has me a bit confused.

I also get the same warning, and it seems to be a known issue. If it is “spurious”, hopefully harmless (false positive)…?

59107 – [8/9/10/11 Regression] Spurious "Type specified for intrinsic function 'command_argument_count' at (1) is ignored" under -Wsurprising.

This is another (very similar) post, related to overloading:
-Wsurprising warning for overloaded intrinsic size

The block method of FortranFan also seems interesting (thanks!), which does not give warning for me (gfortran-10). It might be another possibility to use a local alias (pointer or associate) of the size argument like…

pointer version
module test_m
    implicit none
contains
subroutine sub( size, arr )
    integer, target :: size
    integer :: arr(:)
    integer, pointer :: size_   !! local alias
    size_ => size
    block
    intrinsic :: size

    !( body of the routine )
    print *, size( arr ), size_

    endblock
end
end module

program main
    use test_m
    call sub( size=777, arr=[1,2,3] )
end
associate version
module test_m
    implicit none
contains
subroutine sub( size, arr )
    integer :: size
    integer :: arr(:)
    associate( size_ => size ); block
    intrinsic :: size

    !( body of the routine )
    print *, size( arr ), size_

    end block; end associate
end
end module

program main
    use test_m
    call sub( size=777, arr=[1,2,3] )
end

Inside that subroutine dimtags is a one-dimensional array, and size is a real variable The effect of the intrinsic size(dimtags) can be obtained without using a block and without a name conflict by this, which gave me the same result:
print*, ubound(dimtags,1,c_int)-lbound(dimtage,1,c_int+1_c_int
but please don’t invent yet another local variable called ubound or lbound.

Interesting. I had not thought of the test_m module. When I saw it I was guessing it was non-standard somehow but cannot think of a reason it is, and it worked with three compilers. I made a single program that I think summarizes most of the suggestions; but I am wondering why renaming the variable is not acceptable? The only reason I could think of was that there are calls by keyword that use the name “size” or you really want people to call your routine using “size=VALUE”? Wondering what other reason there could be?

Summary
module M_rename
implicit none
private
public :: size
intrinsic :: size
public :: fsize

contains
! create a wrapper for size() 
function fsize(o) result(sz)
    class(*) :: o(..)
    integer :: sz
    sz = size(o)
end function fsize

end module M_rename

program main
use M_rename, only: fn_size=> size
use M_rename, only : fsize
implicit none
real :: thing(10)
integer :: isz
character(len=*),parameter :: g='(*(g0,1x))'
! obviously, renaming the variable is a way to resolve the conflict
! between size and size, but there are cases (maybe you have calls where
! the routine has been called by name you cannot change) where it would
! be nice to leave the variable named size
  isz=999
! call foo(size=isz)  ;write(*,*)'foo ',isz
  call foo1(size=isz) 
  call foo2(size=isz) 
  call foo3(size=isz) 
  call foo4(size=isz) 
contains
! NO: HAS CONFLICT
!subroutine foo(size)
!    use, intrinsic :: iso_c_binding
!    real(c_double), intent(in) :: size
!    write(*,g) size(thing), size
!end subroutine foo

! RENAME IN PROCEDURE VIA ASSOCIATE AND BLOCK
subroutine foo1(size)
    use, intrinsic :: iso_c_binding
    integer, intent(in) :: size
    ASSOCIATE (VAR_SIZE=>SIZE)
    block
    intrinsic :: size
    write(*,g) 'foo1', size(thing), var_size
    end block
    END ASSOCIATE
end subroutine foo1

! CALL WRAPPER FOR SIZE
subroutine foo2(size)
    use, intrinsic :: iso_c_binding
    integer, intent(in) :: size
    write(*,g) 'foo2',fsize(thing), size
end subroutine foo2

! CALL INTRINSIC IN BLOCK
subroutine foo3(size)
    use, intrinsic :: iso_c_binding
    integer, intent(in) :: size
    block
       intrinsic :: size
       write(*,g,advance='no')'foo3',size(thing)
    end block
    write(*,g) size
end subroutine foo3
  
! PASS-THROUGH (RENAME BY PASSING EVERYTHING THROUGH)
subroutine foo4(size)
    integer, intent(in) :: size
    call foo5(size)
end subroutine foo4
subroutine foo5(siz)
    integer, intent(in) :: siz
    write(*,g)'foo4=>5',size(thing),siz
end subroutine foo5

end program main
1 Like

Thanks for taking the time to form the summary of all the answers @urbanjost, much appreciate it. I think the solution with intrinsic :: size is what I was looking for.

It has to do with the fact that the Fortran API, among many others (C, C++,Julia, Python) is autogenerated, through a Python module, which scans the library’s source code (in C++) and returns the relevant information in terms of some Python classes.

Editing the library’s source code to rename size to something else to get just the Fortran API to work, is not very reasonable. The much more reasonable solution of editing the code generation scripts to rename variables named size only for the Fortran API is actually a non-trivial task at this stage.

In the long term you are probably right, the variables should be renamed, but right now I am trying to get the Fortran API back to a compilable state to make sure it works, and then I can start polishing the code generation script.

Oh, much more complicated problem than I was imagining. So as @kargl mentioned, you have a general name mangling problem where any variable name used in the same scope as a function of that name needs to be unique. So unless you mangle all the variables or all the functions, you will have an issue?

If you are writing human-readable conversions that could get ugly (like adding an underscore suffix to all variable names as a semi-general mangling); but it seems like you will have problems with all languages because of different reserved words or (as in the case of Fortran) the lack of reserved words?

So is the more general case also an issue? If you are translating a code that includes a user procedure “bar()” and some routine that includes a call to “bar()” and a variable “bar” you will generate the same issue? Even just with the intrinsic functions which you could handle with the renaming technique in the accepted solution, there is the issue that different compilers have different extensions so some have additional “intrinsic” names to worry about. Hopefully, your problem is not that generic, but you seem to be generating more than just an ISO_C_BINDING interface.

I will probably abuse the solution myself. I already found myself wrting a rather long equation and used it to rename SIN, COS, and TAN to S, C, and T in a little throw-away code. It will be hard to resist doing that. :slight_smile:

In theory this could be true, but in practice no. All the variable and procedure names are very sensible, the only thing that is causing me grief is size. There is a lot of name mangling going on for almost all languages, but it is internal so the user does not have to deal with it.

Thankfully not, the anatomy of the Fortran API is not very complicated, it’s basically a bunch of static methods. The first couple of iterations were effectively nothing more than callbacks to C wrapped in type-bound procedures.
The problems started when I decided to make the Fortran API more Fortran-like. As in, not returning type(c_ptr)s but Fortran allocatable arrays, or you want to input a Fortran jagged array instead of c_ptrs

You might find my 2020 post about reserved words and naming conflicts of interest: Doctor Fortran in “No Reserve” - Doctor Fortran (stevelionel.com)

2 Likes