Logo Questions Linux Laravel Mysql Ubuntu Git Menu
 

GNU Fortran - controlling symbol case

Is there a way to control the case of symbols emitted by GNU Fortran 4.8?

Older versions (such as 3.4) had -fcase-lower, -fcase-preserve and -fcase-upper to force lower case, the case used in the source and upper case respectively, but these seem to have been discarded. Is there some new way of controlling this?

Edit

I'm trying to port a large, mixed C/Fortran, code base from Intel compilers to GNU compilers.

I'm aware that we can use BIND(C, name='...') to give a case-specific symbol name. However, that has other effects. Consider this C function:

void print(char *str, size_t len) {
    for(int ii = 0; ii < len; ii++) {
        putchar(str[ii]);
    }
    putchar('\n');
}

We can call it from a Fortran program like this:

program test
    implicit none
    interface
        subroutine printstr(str)
            character :: str(*)
        end subroutine
    end interface

    call printstr("Hello, world.");
end

If the C function name is not all lower-case (PrintStr, say) then we might try to fix the Fortran program like this:

program test
    implicit none
    interface
        subroutine printstr(str) bind(C, name='PrintStr')
            use iso_c_binding
            character :: str(*)
        end subroutine
    end interface

    call printstr("Hello, world.");
end

This doesn't work, though, because the bind(C, ...) changes how the string parameter is handled and the length parameter is no longer provided (I'm not sure if this results in stack corruption or just buffer overruns - the example given always segfaults from the buffer overrun).

I think it's probably time for a fresh question on how to sort this out.

like image 466
Tom Avatar asked Oct 14 '14 08:10

Tom


People also ask

Is Fortran 77 case sensitive?

You may wish to mix case, but Fortran is not case-sensitive, so "X" and "x" are the same variable.

Which flags are used for Gfortran to check the array bounds during the run time execution?

-fcheck=all to "enable run-time tests", such as, for instance, array bounds checks.


2 Answers

We have searched high and low for exactly this functionality. In particular, to have case preserved WITHOUT Bind'C. The extreme "shove" introduced by the powers that be to insist on Bind'C is a terrible outcome for many important circumstances, and especially legacy code, and most especially on Windows.

There is NO CHEAP way of porting legacy or Intel etc mixed language code to gFortran, since, as far as we can tell, many years ago the keepers of GNU Fortran explicitly decided they would NOT keep "preserve-case" or anything like it (I forget the bug report, but you can search for it) saying that there was not sufficient interest ... I must say that sounds a little preposterous, as anyone working in a mixed language environment in Windows will almost surely need a preserve case facility with high frequency. This is required in VBA/Fortran for DLL's, required in accessing WinAPI s/r's etc etc., and where Bind'C/ISO causes more problems than fixes.

Similarly, they decided NOT to have an ALIAS or something like that attribute in the compiler directives.

Thus, the ONLY mechanism in gFortran (that we know of) that permits preserving case is Bind'C, which is a DISASTER for a variety of reasons, most especially for passing fixed len strings of len > 1.

We use two different, and highly unsatisfactory, solutions styles for mixed lang/interop with gFortran:

  1. The MUST PRESERVE case case, such as when interfacing to a WinAPI:

    Interface ! Function w32_GetWindowTextW(hWnd, lpString, nMaxCount) bind(C,name="GetWindowTextW") ! ! from c:\Windows\System32\User32.dll ! Use, Intrinsic :: ISO_C_BINDING, Only: c_IntPtr_t, c_Size_t, c_Int, c_Ptr, c_Char ! !GCC$ ATTRIBUTES STDCALL :: w32_GetWindowTextW, hWnd, lpString, nMaxCount ! Integer(c_Int) :: w32_GetWindowTextW Integer(c_IntPtr_t), Value :: hWnd ! NOTE: this is SUPPOSED TO BE a Win HANDLE, this seems ISO equivalent Character(Kind=c_Char) :: lpString(*) Integer(c_Int), Value :: nMaxCount ! NOTE: this is SUPPOSED TO BE WinAPI int type, this seems ISO equivalent End Function w32_GetWindowTextW ! End Interface

Here the preserve case is essential, since otherwise the interface won't find entry point in the WinAPI. Also, the Bind'C allows aliasing that is otherwise not available, for some strange reason, with GCC FPP.

The GCC compiler directives are required to overcome the Bind'C's destruction/alteration of the calling convention, and revert it back to STDCALL, as required with WinAPI (and also with VB, Excel/VBA etc etc).

However, look at the "dogs breakfast" required to deal with lpString var, where it must now be a vector or Len=1's. This is a very expensive re-write (and not only in the declarations, but everywhere those vars are used, at the very least an extra layer must be added to convert the Len=1 char array to the original fixed len char vars).

  1. Case where it would be "nice" to preserve case, but it is "cheaper" to use all lower case, such as with, say VBA/Fortran interop for creating DLL's as Excel Add-Ins.

ASIDE: the following relies on a custom implementation of erf's in our own libs, but quite a good one is available as an intrinsic.

You could go Bind'C and preserve case (with all the "string implications"), such as

Function Erf_Math_BindC_XL(x) bind(C,name="Erf_Math_BindC_XL")
!
Use ARTMathFuncsMod, Only: MathErf  ! Proprietary alternative to Fortran2008 intrinsic Erf()
!
!GCC$ ATTRIBUTES DLLEXPORT, STDCALL :: Erf_Math_BindC_XL
!
Real*8                   :: Erf_Math_BindC_XL
!
Real*8, Intent(In)       :: x
!
Erf_Math_BindC_XL = MathErf(x)
!
End Function Erf_Math_BindC_XL

By comparison, you could use, instead:

Function Erf_Math_XL(x)
!
Use ARTMathFuncsMod, Only: MathErf  ! Proprietary alternative to Fortran2008 intrinsic Erf()
!
!GCC$ ATTRIBUTES DLLEXPORT, STDCALL :: Erf_Math_BindC_XL
!
Real*8                   :: Erf_Math_XL
!
Real*8, Intent(In)       :: x
!
Erf_Math_XL = MathErf(x)
!
End Function Erf_Math_XL

However, if you compile this directly with gFortan the entry name will be decorated and look something like _erf_math_xl@4.

So, if you already had a VBA declaration relying on "Erf_Math_XL", then it will fail.

Now, you can either re-write all of the VBA side ... very expensive, and the "@nn" changes every time you change the arg list, so in reality "geometrically more expensive".

By contrast, if on the gFortran-side you use -fno-underscore, and -mrtd, then the entry names will become simply erf_math_xl . OK, so it is not preserved case, but they are all lower case, and "undecorated". This can be handled in a less expensive manner compared to re-writing many fixed len strings to len=1 arrays, etc.

Then on the VBA-side the Function/Sub declaration do permit ALIAS so the "case issue" is a relatively simple "edit/replace macro"

like image 72
DrOli Avatar answered Oct 11 '22 16:10

DrOli


Here is one way to approach this using the Fotran iso_c_binding module.

First, the C code, just as in your example:

void PrintStr(char *str, size_t len)
{
   for (int ii=0; ii < len; ++ii)
     putchar(str[ii]);
   putchar('\n');
}

and a suitable Fortran interface for it:

interface
  subroutine printstr_c(str, len) bind(C, name='PrintStr')
    use iso_c_binding, only: c_char, c_size_t
    implicit none
    character(kind=c_char) :: str(*)
    integer(c_size_t),value :: len
  end subroutine printstr_c
end interface

This will let you call the C function as:

character(len=20) :: string = 'Hello ISO C env!'
call printstr_c(string, int(len(string),kind=c_size_t))

This works, but requires the length argument to be specified explicitly. We can do a bit better and create a Fortran function wrapper around it to hide the length from callers.

subroutine printstr(str)
  use iso_c_binding, only: c_size_t
  implicit none
  character(len=*) :: str
  call printstr_c(str, int(len(str),kind=c_size_t))
end subroutine

Now we can just call:

character(len=20) :: string = 'Hello ISO C env!'
call printstr(string)

Note that I haven't bothered with null terminating the string as your C function loops over the length argument. If you need a null terminator you could add one in the printstr subroutine.


If you have many such functions you want to call, all of the form void f(str, len), then we can do a bit more work and further abstract the printstr function to just be a generic translator from Fortran character variables to paired char,len variables suitable for an iso_c_binding call. Consider this example:

module cfuncs
  implicit none
  interface
    ! this interface is for an actual C function
    subroutine printstr_c(str, len) bind(C, name='PrintStr')
      use iso_c_binding, only: c_char, c_size_t
      implicit none
      character(kind=c_char) :: str(*)
      integer(c_size_t),value :: len
    end subroutine printstr_c
  end interface
end module

module ffuncs
  use cfuncs
  implicit none
  interface
    ! this interface is to constrain procedures passed to printstr()
    subroutine string_and_len(str, len)
      use iso_c_binding, only: c_char, c_size_t
      implicit none
      character(kind=c_char) :: str(*)
      integer(c_size_t),value :: len
    end subroutine string_and_len
  end interface
contains
  ! this routine takes the C function you want to call and a string to pass
  ! and does the translation to call funct(str,len)
  subroutine printstr(func,str)
    use iso_c_binding, only: c_size_t
    implicit none
    procedure(string_and_len) :: func
    character(len=*) :: str
    call func(str, int(len(str),kind=c_size_t))
  end subroutine
end module

program main
  use ffuncs
  implicit none
  character(len=20) :: string = 'Hello ISO C env!'
  call printstr(printstr_c, string)
end program

This is perhaps a bit overkill for this specific example, but it lets one Fortran wrapper call many C functions of the same type signature. This in turn would only require you to decorate the Fortran calls in the code you are porting to be wrapped by the wrapper function. For example assuming printstrc_c is the foreign interface:

! old F77 non iso_c_binding call
call printstr_c("Hello World")

turns into

! wrapping the old F77 call through our Fortran wrapper handling iso_c_binding
call printstr(printstr_c, "Hello World")

This isn't as elegant looking as the old way you were doing things, but the new versions of gfortran (3.x gcc was g77, and 4.x is gfortran, afaik a complete rewrite) don't seem to be able to force case preservation. If you wanted to avoid the mess I demonstrated, another option would be to post-process the compiled Fortran objects prior to linking and rewrite the function names to have proper case, but I'd consider that a worse mess to deal with (and a dirty hack).

like image 37
casey Avatar answered Oct 11 '22 16:10

casey