Here is a module defining a derived type that essentially makes a copy of the command-line arguments:
! c_args.f90
module c_args
use, intrinsic :: iso_c_binding
implicit none
private
public :: args
public :: destroy_args
public :: print_args
!> C-compatible command line arguments
type :: args
integer(c_int) :: argc
type(c_ptr) :: argv
contains
end type
! A few routines from libc are needed
interface
function c_malloc(size) bind(c,name="malloc")
import c_size_t, c_ptr
integer(c_size_t), value :: size
type(c_ptr) :: c_malloc
end function
subroutine c_free(ptr) bind(c,name="free")
import c_ptr
type(c_ptr), value :: ptr
end subroutine
!> size_t strlen ( const char * str )
function c_strlen(str) bind(c,name="strlen")
import c_size_t, c_ptr
type(c_ptr), value :: str
integer(c_size_t) :: c_strlen
end function
end interface
!> Overloaded structure-constructor
interface args
module procedure new_args
end interface
contains
!> Initialize the derived type with a copy of the command-line arguments
function new_args() result(this)
type(args) :: this
type(c_ptr), pointer :: argv(:)
integer :: i, l
this%argc = command_argument_count()
this%argv = c_malloc( this%argc * c_sizeof(this%argv) )
call c_f_pointer(this%argv, argv, [this%argc])
do i = 1, this%argc
call get_command_argument(i,length=l)
argv(i) = c_malloc( (l+1) * c_sizeof(c_null_char) )
block
character(len=l+1,kind=c_char), pointer :: str
call c_f_pointer(argv(i), str)
call get_command_argument(i,value=str)
str(l+1:l+1) = c_null_char
end block
end do
end function
subroutine destroy_args(this)
type(args), intent(inout) :: this
integer :: i
type(c_ptr), pointer :: argv(:)
call c_f_pointer(this%argv, argv, [this%argc])
do i = 1, this%argc
call c_free(argv(i))
end do
call c_free(this%argv)
end subroutine
subroutine print_args(this)
type(args), intent(in) :: this
integer :: i
integer(c_size_t) :: l
type(c_ptr), pointer :: argv(:)
call c_f_pointer(this%argv, argv, [this%argc])
write(*,'(A)') "Printing from Fortran"
do i = 1, this%argc
l = c_strlen(argv(i))
block
character(len=l,kind=c_char), pointer :: str
call c_f_pointer(argv(i), str)
write(*,'(A)') str
end block
end do
end subroutine
end module
Using the derived type, we can easily pass the arguments to C:
! main_args.f90
program main_args
use c_args
implicit none
interface
!> void print_from_c(int *argc, char **argv);
subroutine print_from_c(argc,argv) bind(c)
use, intrinsic :: iso_c_binding, only: c_int, c_ptr
integer(c_int) :: argc
type(c_ptr), value :: argv
end subroutine
end interface
type(args) :: myargs
myargs = args()
call print_from_c(myargs%argc,myargs%argv) ! C
call print_args(myargs) ! Fortran
call destroy_args(myargs) ! Don't forget, otherwise memory leak
end program
// print_from_c.c
#include <stdio.h>
void print_from_c(int *argc, char **argv)
{
puts("Printing from C");
for (int i = 0; i < *argc; ++i) {
puts(argv[i]);
}
}
~/fortran/cmd$ make main_args
gfortran -Wall -c c_args.f90
gcc -Wall -c print_from_c.c
gfortran -Wall -o main_args main_args.f90 c_args.o print_from_c.o
~/fortran/cmd$ ./main_args a b c
Printing from C
a
b
c
Printing from Fortran
a
b
c
This should in principle work even with an underlying command-line mechanism that is not based on a C runtime library. In a parallel universe where a Fortran-based OS appears, we might have:
program main ! The Fortran "main", wrapping a C "main"
use c_args
implicit none
interface
!> int main(int argc, char **argv)
function main__(argc, argv) bind(c,name="MAIN__") ! The C Main
use, intrinsic :: iso_c_binding, only: c_int, c_ptr
integer(c_int), value :: argc
type(c_ptr), value :: argv
integer(c_int) :: main
end function
end interface
type(args) :: fargs
integer(c_int) :: ret
fargs = args()
ret = main__(fargs%argc,fargs%argv)
stop ret, quiet=.true.
end program
Anyways, I suppose the ugly work of writing the wrapper is better than the alternative where N libraries XYZ
would need to implement a XYZ_Init()
routine using Fortran intrinsics under the hood, and not the int argc, char **argv
mechanism. The former is an overhead of O(1), the latter of O(N).