Finding the length of Fortran allocatable character string - fortran

How could I find the size of a dynamically allocated object path in subroutine newcase?
subroutine newcase(path)
character(:, kind=c_char),
& allocatable :: path
integer(kind=c_int) :: sizepath
write(*,*) "Trim Path: ", path, ":"
this% object = newcase_c(path, sizepath)
end subroutine newcase
The object is allocated when the subroutine is called as shown below:
character(256, kind=c_char) :: cwd
character(:, kind=c_char)
& , allocatable :: trimpath
call GETCWD(cwd)
trimpath = trim(cwd)
call newcase(trimpath)

I used len to find the length of path. Documentation is here.

Related

reading different files from the subroutine depending on the input

I have a piece of code in fortran. I have the files dumped in subroutine. Now I want to call the specific file from the subroutine which depends on m. for eg if m=3 it should read filename(3) and if m=6 it should read filename(6). It is simply not working. Can somebody help me to fix this?
Program main
implicit none
integer,parameter :: dp=kind(1.d0)
real,parameter::m=3
real(dp), dimension(:,:), allocatable :: s
call My_Reader(m)
allocate (s(m,m))
read(m*10,*) s
print*,s
SUBROUTINE My_Reader(m)
integer,parameter :: dp=kind(1.d0)
character (len=256)::filename(m)
integer , intent(in) :: m
filename(6)='C:\Users\spaudel\Documents\S6.txt'
filename(3)='C:\Users\spaudel\Documents\S3.txt'
OPEN (unit=m*10,FILE=fileName(m),status='old', action='read')
END SUBROUTINE My_Reader
in the above program it should print s( my filename is m*m matrix) but sometimes it prints sometimes not. I am using gfortran.
The length of the filename array is given as (m), which is the dummy argument for which of the files you want to read.
So if, for example, you call My_Reader(3), it will only initialize a 3-element array for filename and then anything can happen when you write something to the 6th element.
You could simply fix the size of the filename array in the subroutine declaration block:
character(len=256) :: filename(6)
but I would do something completely different, I'd use a select case to assign the filename in the subroutine:
subroutine my_reader(m)
integer, intent(in) :: m
character(len=256) :: filename
select case (m)
case(3)
filename = 'C:\Users\spaudel\Documents\S3.txt'
case(6)
filename = 'C:\Users\spaudel\Documents\S6.txt'
case default
print *, 'incorrect selection of file number: `, m
STOP
end select
open(unit=m*10, file=filename, ...)
end subroutine my_reader

passing allocatable character through two levels of procedure calls fails

I am experiencing an allocation failure when using allocatable character strings as optional arguments. The problem only occurs when I call through two levels of procedures. In my actual code call get_level1() (see below) represents a call to a list data structure and call get_level2() represents the list calling the same type of accessor function on one of its records. I have stripped down an example to the bare minimum that adequately reproduces the problem.
In the code below when I call get_level2 directly the expected character string is returned through the optional argument. When I call get_level1 which in turn calls get_level2 allocation of the optional dummy argument fails. Using gdb I find the allocation attempt to create a character*1635... when it gets back to the actual argument is obviously has an integer overflow because it thinks the allocation is character*-283635612...
My actual code has many optional arguments not just one. As a simple example I added an optional integer argument. This time instead of a segmentation fault I get a null string.
In the second example the integer argument works regardless of using the character argument. (I would expect this since no dynamic allocation is being performed) The integer's presence has no effect on the character. I have also tried changing the intent to (inout). This does not change the behavior, though I did not expect it to. [I believe that intent(out) causes the actual argument to deallocate first, and intent(inout) retains the actual argument's allocation state]
call get_level1( NUM=n ) ! works
call get_level1( NUM=n, TEXT=words ) ! fails
call get_level1( TEXT=words ) ! fails
my compile cmd is:
gfortran -Wall -g -std=f2008ts stest1.f08 -o stest
Environment
Linux 4.15.0-42-generic #45-Ubuntu SMP x86_64 GNU/Linux
GNU Fortran (Ubuntu 7.3.0-27ubuntu1~18.04) 7.3.0
Example with one optional argument
module stest1
implicit none
character(:), allocatable :: data
contains
subroutine get_level2( TEXT )
implicit none
character(:), optional, allocatable, intent(out) :: TEXT
if ( PRESENT( TEXT ) ) then
TEXT = 'Prefix: ' // data // ' :postfix'
end if
end subroutine get_level2
subroutine get_level1( TEXT )
implicit none
character(:), optional, allocatable, intent(out) :: TEXT
call get_level2( TEXT )
end subroutine get_level1
end module stest1
program main
use stest1
implicit none
character(:), allocatable :: words
data = 'Hello Doctor'
call get_level1( words )
write(*,100) words
100 format( 'words = [',A,']' )
end program main
Example with two optional arguments
module stest2
implicit none
character(:), allocatable :: data
integer :: count
contains
subroutine get_level2( TEXT, NUM )
implicit none
character(:), optional, allocatable, intent(out) :: TEXT
integer, optional, intent(out) :: NUM
if ( PRESENT( TEXT ) ) then
TEXT = 'Prefix: ' // data // ' :postfix'
end if
if ( PRESENT( NUM ) ) then
NUM = count
end if
end subroutine get_level2
subroutine get_level1( TEXT, NUM )
implicit none
character(:), optional, allocatable, intent(out) :: TEXT
integer, optional, intent(out) :: NUM
call get_level2( NUM=NUM, TEXT=TEXT )
end subroutine get_level1
end module stest2
program main
use stest2
implicit none
character(:), allocatable :: words
integer :: n
count = 42
data = 'Hello Doctor'
call get_level1( TEXT=words )
write(*,100) words
write(*,110) n
100 format( 'words = [',A,']' )
110 format( 'N = [',I0,']' )
end program main
You seem to have hit a compiler bug. I can reproduce the issue on gfortran 8.2.1:
Operating system error: Cannot allocate memory
Memory allocation failure in xrealloc
Error termination. Backtrace:
#0 0x7f9c0314f107 in write_character
at ../../../libgfortran/io/write.c:1399
#1 0x7f9c03153e66 in list_formatted_write_scalar
at ../../../libgfortran/io/write.c:1872
#2 0x400c78 in MAIN__
at /tmp/test.F90:43
#3 0x400cbe in main
at /tmp/test.F90:34
but in 5.1.1 I see the correct output:
Prefix: Hello Doctor :postfix
With the following work-around, I got it to work:
subroutine get_level1( TEXT )
implicit none
character(:), optional, allocatable, intent(out) :: TEXT
character(:), allocatable :: tmp
if ( PRESENT( TEXT ) ) then
call get_level2( tmp )
TEXT = tmp
else
call get_level2( )
endif
end subroutine get_level1
It is a bug in the compiler, and still stands in gfortran v9.0.0 (experimental) on Windows. You should report it with the vendor.
I've done some tests and it seems that the failure only happens when: passing a present optional argument as an actual argument corresponding to a dummy argument that is character(:), allocatable, optional. Any variation in the previous sentence seems to avoid the bug and produce the correct result.
I reduced your example to a minimal test-case:
program main
implicit none
character(:), allocatable :: txt
call sub1(txt)
print *, "main ", len(txt), txt ! prints: main 0 (or throws segfault)
contains
subroutine sub1(txt)
character(:), allocatable, optional :: txt
call sub2(txt)
print *, "sub1 ", len(txt), txt ! prints: sub1 0 (or throws segfault)
end
subroutine sub2(txt)
character(:), allocatable, optional :: txt
if(present(txt)) txt = "message"
print *, "sub2 ", len(txt), txt ! prints: sub2 7 message
end
end
The inspection inside sub2 shows that the assignment actually works there. The problem seems to happen when associating that dummy to the actual argument inside sub1. Hmm...
Again, any variation of the pattern character(:), allocatable, optional dummies produces the correct result in my tests. So, I suggest you to flexibilize at least one of the previous conditions to circumvent the buggy thing. There are some suggestions:
1. non-allocatable optional character works, no matter if fixed or assumed length;
Here is an example with fixed-lenght variable and assumed-length arguments.
Advantage: Easy to refactor, less disruptive/intrusive.
Disadvantage: Must estimate the length of the variable beforehand, wastes storage.
program option1
implicit none
character(10) :: txt
call sub1(txt)
print *, "main ", len(txt), txt ! prints: main 10 message
contains
subroutine sub1(txt)
character(*), optional :: txt
call sub2(txt)
print *, "sub1 ", len(txt), txt ! prints: sub1 10 message
end
subroutine sub2(txt)
character(*), optional :: txt
if(present(txt)) txt = "message"
print *, "sub2 ", len(txt), txt ! prints: sub1 10 message
end
end
2. non-optional, on either the actual argument passed from sub1 or on the dummy argument in sub2, also makes it work;
Of course, if you can refactor your code to avoid this situation, that would be the better solution. You could use generic interfaces to achieve a similar result, for example. Or, as you said in the comment, "using local variables at level1 and passing all the optional arguments to the lower level".
Disadvantage: May need to change interfaces of the lower-level procedures.
Advantage: Wouldn't be a problem if they are private module procedures; It's an implementation detail.
Consider the following approach, that hacks the bug and avoid passing an optional argument, so doesn't change the procedure's signature:
program option2
implicit none
character(:), allocatable :: txt
call sub1(txt)
print *, "main ", len(txt), txt ! prints: main 7 message
contains
subroutine sub1(txt)
character(:), allocatable, optional :: txt
character(:), allocatable :: txt_
if(present(txt)) then
! txt_ isn't optional, so the bug doesn't fire
call sub2(txt_)
txt = txt_
end if
print *, "sub1 ", len(txt), txt ! prints: sub1 7 message
end
subroutine sub2(txt)
character(:), allocatable, optional :: txt
print *, present(txt)
if(present(txt)) txt = "message"
print *, "sub2 ", len(txt), txt ! prints: sub2 7 message
end
end
3. with any other type it works too, no matter the attributes (even a derived-type with allocatable character component). Although, changes on the rank or kind don't count.
I will show you two options involving derived types: one with allocatable character length component; the other with parameterized derived type.
Advantage: You can keep your code structure, and all the optional stuff. Storage overhead is low. You could even extend your DT with methods and tailor it to your problem.
Disadvantage: Maybe too much hassle for little. PDT is cool, but is a new (and buggy) feature in gfortran.
program option3a
! using a derived type with allocatable character length component.
implicit none
type :: string
character(:), allocatable :: chars
end type
type(string) :: txt
call sub1(txt)
print *, "main ", len(txt%chars), txt%chars ! prints: main 7 message
contains
subroutine sub1(txt)
type(string), optional :: txt
call sub2(txt)
print *, "sub1 ", len(txt%chars), txt%chars ! prints: sub1 7 message
end
subroutine sub2(txt)
type(string), optional :: txt
if(present(txt)) txt = string("message")
print *, "sub2 ", len(txt%chars), txt%chars ! prints: sub2 7 message
end
end
program option3b
! using a parameterized derived type, you can practically mimic the intrinsic
! character type behavior, with the possibility to add custom behavior.
! but its still raw in gfortran.
implicit none
type :: string(len)
integer, len :: len
character(len) :: chars
end type
type(string(:)), allocatable :: txt
call sub1(txt)
print *, "main ", txt%len, txt ! prints: main 7 7 message (a lil bug of gfortran)
contains
subroutine sub1(txt)
type(string(:)), allocatable, optional :: txt
call sub2(txt)
print *, "sub1 ", txt%len, txt ! prints: main 7 7 message
end
subroutine sub2(txt)
type(string(:)), allocatable, optional :: txt
! the following fails with gfortran, however it's valid syntax
! if(present(txt)) txt = string(7)("message")
allocate(string(7) :: txt)
if(present(txt)) txt%chars = "message"
print *, "sub2 ", txt%len, txt ! prints: main 7 7 message
end
end
Summing up: you can change your compiler or choose any of those (or other) way to circunvent this bug and keep working, until your compiler vendor address the issue.

NetCDF: Start+count exceeds dimension bound

I have written a code in Fortran to read a NetCDF file that has 4-d data [time, level,longitude,latitude]. However, my code yields an error
NetCDF: Start+count exceeds dimension bound
on any 4-d NetCDF file I am using. For example, the file at http://people.sc.fsu.edu/~jburkardt/f_src/netcdf/pres_temp_4D.nc has pressure and temperature. I paste my code below. Please suggest what is going wrong.
PROGRAM rw_nc4d_main
USE rw_nc4d, ONLY: read_nc4
IMPLICIT NONE
CHARACTER(LEN=50) :: ncfn
CHARACTER(LEN=15) :: vname
ncfn = 'pres_temp_4D.nc'
vname = 'pressure'
CALL read_nc4(ncfn, vname)
END PROGRAM rw_nc4d_main
!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
MODULE rw_nc4d
USE netcdf
IMPLICIT NONE
CONTAINS
SUBROUTINE read_nc4(fname,vin_name)
IMPLICIT NONE
CHARACTER(LEN=*), INTENT(IN) :: fname
CHARACTER(LEN=*), INTENT(IN) :: vin_name
! Local variables
INTEGER :: ncid, var_id, ndim, nvar, nattr, unlim_id
CHARACTER(LEN=15) :: dname
INTEGER :: dlength
INTEGER :: ii, status, lx, ly, lz, lt, lzp1
REAL :: sf, ofs
REAL, DIMENSION(:,:,:,:), ALLOCATABLE :: vin
CALL nc_check(nf90_open(fname, nf90_nowrite, ncid))
CALL nc_check(nf90_inquire(ncid,ndim,nvar))
DO ii = 1, ndim
CALL nc_check(nf90_inquire_dimension(ncid,ii,dname,len=dlength))
SELECT CASE(TRIM(dname))
CASE('lon', 'LON', 'longitude')
lx = dlength
CASE('lat', 'LAT', 'latitude' )
ly = dlength
CASE('lev', 'LEV', 'level' )
lz = dlength
CASE('time', 'TIME' )
lt = dlength
CASE('ilev', 'ILEV')
lzp1 = dlength
CASE DEFAULT
WRITE(*,*)'ERROR: nc_check for dimensions!'; STOP
END SELECT
END DO
ALLOCATE(vin(lt,lz,ly,lx))
CALL nc_check(nf90_inq_varid(ncid,TRIM(vin_name),var_id))
CALL nc_check(nf90_get_var(ncid,var_id,vin,start=(/1,1,1,1/),count=(/lt,lz,ly,lx/)),fname=TRIM(fname))
END SUBROUTINE read_nc4
SUBROUTINE nc_check(status,fname)
INTEGER, INTENT(IN) :: status
CHARACTER(LEN=*), OPTIONAL :: fname
IF (status /= nf90_noerr) THEN
IF (PRESENT(fname)) THEN
WRITE(*,*)'FATAL ERROR in ',TRIM(fname),' ',TRIM(nf90_strerror(status))
ELSE
WRITE(*,*)'FATAL ERROR: ',TRIM(nf90_strerror(status))
END IF
STOP
END IF
END SUBROUTINE nc_check
END MODULE rw_nc4d
You have the dimensions back to front. I also suspect that your variable has the longitude and latitude in the reverse order to which you have posted. A variable with shape [time, level,latitude,longitude] should be declared as var(longitude, latitude, level, time) in Fortran.

How to format to a string with minimum possible size

I have the following function:
function fname(proc, ct) result(filename)
implicit none
integer, intent(in) :: proc, ct
character(len=100) :: filename
write(filename,"(a,i9.9,a,i0,a)") "/step", ct, "-proc", proc, ".txt"
end function fname
In modern Fortran, is there an automatic way to have the resulting string to have the minimum possible size to fit all the formatted data? Notice the use of i0 format makes the size of the resulting string variable.
It is possible, but not directly in the read statement. If you wrap the integer to string conversion into a function:
function itoa(i) result(res)
character(:),allocatable :: res
integer,intent(in) :: i
character(range(i)+2) :: tmp
write(tmp,'(i0)') i
res = trim(tmp)
end function
you can then use allocatable deferred-length string
character(:), allocatable :: filename
filename = "/step" // itoa99(ct) // "-proc" // itoa(proc) // ".txt"
You can adjust the function, to take the integer format as a dummy argument instead of making more versions of it.
The other possibility is to have a large temporary string and trim it
character(100) :: tmp
character(:), allocatable :: filename
write(tmp,"(a,i9.9,a,i0,a)") "/step", ct, "-proc", proc, ".txt"
filename = trim(tmp)

Calling METIS API(wrtten in C language) in fortran program

Over 2 weeks, I've struggled to call one of the METIS library written in C from my fortran code. And, unfortunately, It doesn't seem to be a HAPPY END without your help. I found some posts about direct calling and using interface. I prefer the latter because I could monitor the variables for debugging. There are three codes I attached.
1. c function I'd like to use 2. fortran interface module 3. fortran program
(1) c function
int METIS_PartMeshNodal(idx_t *ne, idx_t *nn, idx_t *eptr, idx_t *eind,
idx_t *vwgt, idx_t *vsize, idx_t *nparts, real_t *tpwgts,
idx_t *options, idx_t *objval, idx_t *epart, idx_t *npart)
I removed the c funciton body. It's not necessary to understand my problem
Here, idx_t is integer and real_t is single or double precision. From ne to options are input and last three arguments are output. And vwgt, vsize, tpwgts and options can receive null as an input for default setting I wrote the interface module for using c function like this
(2) Fortran interface module
Fixed!
Insert use iso_c_bind under use constants
Use integer(c_int) instead of integer for ne, nn and other variables.
Remove unused module constants
.
module Calling_METIS
!use constants, only : p2 !this is for double precision
use iso_c_bind !inserted later
implicit none
!integer :: ne, nn !modified
integer(c_int) :: ne, nn
!integer, dimension(:), allocatable :: eptr, eind !modified
integer(c_int), dimension(:), allocatable :: eptr, eind
!integer, dimension(:), allocatable :: vwgt, vsize !modified
type(c_ptr) :: vwgt, vsize
!integer :: nparts !modified
integer(c_int) :: nparts
!real(p2), dimension(:), allocatable :: tpwgts !modified
type(c_ptr) :: tpwgts
!integer, dimension(0:39) :: opts !modified
integer(c_int), dimension(0:39) :: opts
!integer :: objval !modified
integer(c_int) :: objval
!integer, dimension(:), allocatable :: epart, npart !modified
integer(c_int), dimension(:), allocatable :: epart, npart
interface
subroutine METIS_PartMeshNodal( ne, nn, eptr, eind, vwgt, vsize, nparts, tpwgt, &
opts, objval, epart, npart) bind(c)
use intrinsic :: iso_c_binding
!use constants, only : p2
implicit none
integer (c_int), intent(in) :: ne, nn
integer (c_int), dimension(*), intent(in) :: eptr, eind
!integer (c_int), dimension(*), intent(in) :: vwgt, vsize !modified
type(c_ptr), value :: vwgt, vsize
integer (c_int), intent(in) :: nparts
!real(c_double), dimension(*), intent(in) :: tpwgt !modified
type(c_ptr), value :: tpwgt
integer (c_int), dimension(0:39), intent(in) :: opts
integer (c_int), intent(out) :: objval
integer (c_int), dimension(*), intent(out) :: epart
integer (c_int), dimension(*), intent(out) :: npart
end subroutine METIS_PartMeshNodal
end interface
end module
And here is my program code calling the function
(3) Fortran program
Fixed!
allocation size of npart is fixed. Not ne but nn
opts(7)=1 is added to get Fortran-style array of epart, npart(no effect until now)
.
program METIS_call_test
!some 'use' statments
use Calling_METIS
use iso_c_binging !added
implicit none
! Local variable
integer :: iC
character(80) :: grid_file !grid_file
grid_file = 'test.grid'
! (1) Read grid files
call read_grid(grid_file)
! (2) Construction Input Data for calling METIS Function
! # of cells, vertices
ne = ncells
nn = nvtxs
! eptr, eind allocation
allocate(eptr(0:ne), eind(0:3*ntria + 4*nquad - 1))
! eptr and eind building
eptr(0) = 0
do iC=1, ncells
eptr(iC) = eptr(iC-1) + cell(iC)%nvtxs
eind(eptr(iC-1):eptr(iC)-1) = cell(iC)%vtx
end do
! epart, npart building
!allocate(epart(ne), npart(ne))
allocate(epart(ne), npart(nn)) ! modified
! # of partition setting
nparts = 2
vwgt = c_null_ptr !added
vsize = c_null_ptr !added
tpwgt = c_null_ptr !added
! (3) Call METIS_PartMeshNodal
call METIS_SetDefaultOptions(opts)
opts(7) = 1 !Added. For fortran style output array epart, npart.
call METIS_PartMeshNodal(ne, nn, eptr, eind, vwgt, vsize, nparts, tpwgt, &
opts, objval, epart, npart)
!call METIS_PartMeshNodal(ne, nn, eptr, eind, null(), null(), nparts, null(), &
! opts, objval, epart, npart) !wrong...
end program
But the problem is that I get an error message as below though I put null for tpwgt.
Input Error: Inorrect sum of 0.000000 for tpwgts for constraint 0.
And this message is handled in the code below.
for (i=0; i<ctrl->ncon; i++) {
sum = rsum(ctrl->nparts, ctrl->tpwgts+i, ctrl->ncon);
if (sum < 0.99 || sum > 1.01) {
IFSET(dbglvl, METIS_DBG_INFO,
printf("Input Error: Incorrect sum of %"PRREAL" for
tpwgts for constraint %"PRIDX".\n", sum, i));
return 0;
}
}
Anyway, in order to see what I would get if I put an array for tpwgts intead of null, tpwgts(:) = 1.0/nparts, which makes sum of tpwgts equal 1.0. But I got same message with 1.75 for the sum.
These are my questions
1. Did I use null() for passing arguments correctly?
2. Do I have to pass pointers for all arguments to c function? then how?
3. Is putting an integer to opts(0:39) enough for use? For example, in a post without 'interface module', simple code like options(3)=1 is used. But in the c code, options has 16 named variable like options[METIS_OPTION_NUMBERING], options[METIS_OPTION_UFACTOR]. I think some thing is necessary to set options but I have no idea.
4. Is there an example for METIS in fortran?
Any kind of hint/advice will be a great help for me. Thank you.
Conclution
The problem I had was that c function couldn't recognize null pointer from fortran code.
There were some miss declations of variables in interface module(see 'Fixed' and comments)
It looks like the code works properly. But option(7) = 1 for fortran style output didn't work and now I'm looking at it.
No, you cannot pass null(), that is a Fortran pointer constant. You must pass C_NULL_PTR from the module ISO_C_BINDING and the interface must reflect this. The dummy argument must be type(c_ptr), most probably with VALUE attribute. It may actually work because of the same internal representation, but I wouldn't count on it.
No, if you pass some normal variable, you can pass it directly by reference. Just like normally in Fortran. If the interface is BIND(C), the compiler knows it must send a pointer.
There is a new TS to update Fortran 2008, where you can define dummy arguments in the interoperable procedures as OPTIONAL. Then you can pass the null pointer just by omitting them. Gfortran should already support this.
Note: Here I can see a much different C signature of your function, are you sure yours is OK? http://charm.cs.uiuc.edu/doxygen/charm/meshpart_8c.shtml
I think your opts(7) does not work because you also need an interface for the METIS function METIS_SetDefaultOptions. Based on the answer from http://glaros.dtc.umn.edu/gkhome/node/877, I created a wrapper module (metisInterface.F90) with the interfaces I needed:
module metisInterface
! module to allows us to call METIS C functions from the main Fortran code
use,intrinsic :: ISO_C_BINDING
integer :: ia,ic
integer(C_INT) :: metis_ne,metis_nn
integer(C_INT) :: ncommon,objval
integer(C_INT) :: nparts
integer(C_INT),allocatable,dimension(:) :: eptr,eind,perm,iperm
integer(C_INT),allocatable,dimension(:) :: epart,npart
type(C_PTR) :: vwgt,vsize,twgts,tpwgts
integer(C_INT) :: opts(0:40)
interface
integer(C_INT) function METIS_SetDefaultOptions(opts) bind(C,name="METIS_SetDefaultOptions")
use,intrinsic :: ISO_C_BINDING
implicit none
integer(C_INT) :: opts(0:40)
end function METIS_SetDefaultOptions
end interface
interface
integer(C_INT) function METIS_PartMeshDual(ne,nn,eptr,eind,vwgt,vsize,ncommon,nparts,tpwgts, &
opts,objval,epart,npart) bind(C,name="METIS_PartMeshDual")
use,intrinsic :: ISO_C_BINDING
implicit none
integer(C_INT):: ne, nn
integer(C_INT):: ncommon, objval
integer(C_INT):: nparts
integer(C_INT),dimension(*) :: eptr, eind
integer(C_INT),dimension(*) :: epart, npart
type(C_PTR),value :: vwgt, vsize, tpwgts
integer(C_INT) :: opts(0:40)
end function METIS_PartMeshDual
end interface
end module metisInterface
Then, in the main program (or wherever you make the call to the METIS functions) you need to have (for completeness, I also added the call to METIS_PartMeshDual):
use metisInterface
integer :: metis_call_status
.
.
.
metis_call_status = METIS_SetDefaultOptions(opts)
! METIS_OPTION_NUMBERING for Fortran
opts(17) = 1
metis_call_status = METIS_PartMeshDual(metis_ne,metis_nn,eptr,eind, &
vwgt,vsize,ncommon,nparts,tpwgts,opts,objval,epart,npart)
Note that epart and npart will have Fortran numbering as you want (starting at 1). However, the processors will also start numbering at 1. For example, if you are running in 4 processors, root processor is 1 and you may have epart(n)=4, and you will not have any epart(n)=0.
Finally, a file metis.c is also needed with a single line:
#include "metis.h"
Compiling instructions
Compile metis.c with a C compiler
Compile metisInterface.F90 with a Fortran compiler linking with the compiled C object
Compile main program with a Fortran compiler linking with metisInterface.o