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

人盡茶涼 提交于 2019-11-27 08:31:49

问题


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!

  1. Insert use iso_c_bind under use constants
  2. Use integer(c_int) instead of integer for ne, nn and other variables.
  3. 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!

  1. allocation size of npart is fixed. Not ne but nn
  2. 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.


回答1:


  1. 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.

  2. 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




回答2:


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

  1. Compile metis.c with a C compiler
  2. Compile metisInterface.F90 with a Fortran compiler linking with the compiled C object
  3. Compile main program with a Fortran compiler linking with metisInterface.o


来源:https://stackoverflow.com/questions/14730349/calling-metis-apiwrtten-in-c-language-in-fortran-program

易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!