51          (elmdist, eptr, eind, elmwgt, wgtflag, numflag, ncon, &
 
   52          ncommonnodes, nparts, tpwgts, ubvec, options, edgecut, part) &
 
   53          bind(c, name=
'ParMETIS_V3_PartMeshKway_wrapper')
 
   54       use, 
intrinsic :: iso_c_binding
 
   57       type(c_ptr), 
value :: elmdist, eptr, eind, elmwgt, wgtflag, &
 
   58            numflag, ncon, ncommonnodes, nparts, options, edgecut, part
 
   60       type(c_ptr), 
value :: tpwgts, ubvec
 
 
  111    type(
mesh_t), 
intent(inout) :: msh
 
  113    type(
mesh_fld_t), 
intent(in), 
optional :: weights
 
  114    integer, 
intent(in), 
optional :: nprts
 
  115    integer(kind=M_INT), 
target :: wgtflag, numflag, ncon, ncommonnodes
 
  116    integer(kind=M_INT), 
target :: nparts, options(3), edgecut, rcode
 
  117    real(kind=m_real), 
allocatable, 
target, 
dimension(:) :: tpwgts, ubvec
 
  118    integer(kind=M_INT), 
allocatable, 
target, 
dimension(:) :: &
 
  119         elmdist, eptr, eind, elmwgt, part
 
  120    integer :: i, j, k, ierr
 
  127    ncommonnodes = 2**(msh%gdim - 1)
 
  133    if (
present(nprts)) 
then 
  139    allocate(elmdist(0:
pe_size), eptr(0:msh%nelv))
 
  140    allocate(eind(0:(msh%nelv * msh%npts)), part(msh%nelv))
 
  141    allocate(elmwgt(msh%nelv), tpwgts(ncon * nparts), ubvec(ncon))
 
  145    if (
present(weights)) 
then 
  146       call parmetis_wgt(msh, elmwgt, tpwgts, ubvec, nparts, ncon, weights)
 
  148       call parmetis_wgt(msh, elmwgt, tpwgts, ubvec, nparts, ncon)
 
  153       eptr(i) = parmetis_idx(eptr(i - 1) + msh%npts)
 
  159          eind(k) = parmetis_idx(msh%elements(i)%e%pts(j)%p%id() - 1)
 
  165         c_loc(elmwgt), c_loc(wgtflag), c_loc(numflag), c_loc(ncon), &
 
  166         c_loc(ncommonnodes), c_loc(nparts), c_loc(tpwgts), c_loc(ubvec),&
 
  167         c_loc(options), c_loc(edgecut), c_loc(part))
 
  175    deallocate(elmdist, eptr, eind, part, elmwgt, tpwgts, ubvec)
 
 
  182    type(
mesh_t), 
intent(inout) :: msh
 
  184    integer(kind=M_INT), 
target :: ndims
 
  185    real(kind=m_real), 
allocatable, 
target, 
dimension(:) :: xyz
 
  186    integer(kind=M_INT), 
allocatable, 
target, 
dimension(:) :: vtxdist, part
 
  188    integer :: i, j, ierr, rcode
 
  192    allocate(part(msh%nelv), xyz(ndims * msh%nelv))
 
  199       c = msh%elements(j)%e%centroid()
 
  200       xyz(i) = parmetis_real(c%x(1))
 
  201       xyz(i + 1) = parmetis_real(c%x(2))
 
  202       xyz(i + 2) = parmetis_real(c%x(3))
 
  207         c_loc(xyz), c_loc(part))
 
  215    deallocate(part, xyz, vtxdist)
 
 
  236    type(
mesh_t), 
intent(in) :: msh
 
  237    integer(kind=M_INT), 
allocatable, 
intent(inout) :: wgt(:)
 
  238    real(kind=m_real), 
allocatable, 
intent(inout) :: tpwgts(:)
 
  239    real(kind=m_real), 
allocatable, 
intent(inout) :: ubvec(:)
 
  240    integer, 
intent(in) :: nparts, ncon
 
  241    type(
mesh_fld_t), 
intent(in), 
optional :: weight
 
  244    if (
present(weight)) 
then 
  246          wgt(i) = parmetis_idx(weight%data(i))
 
  249       wgt = parmetis_idx(1)
 
  252    do i = 1, (ncon * nparts)
 
  253       tpwgts(i) = parmetis_real(1) / parmetis_real(nparts)
 
  257       ubvec(i) = parmetis_real(1.05d0)
 
 
subroutine, public parmetis_partmeshkway(msh, parts, weights, nprts)
Compute a k-way partitioning of a mesh msh.
 
subroutine parmetis_wgt(msh, wgt, tpwgts, ubvec, nparts, ncon, weight)
Setup weights and balance constraints for the dual graph.