I am working on an interface to the nanoflann library for N-nearest neighbor searches in two- and three-dimensions. This is a header-only library written in C++.
I have faced a few issues in the process, and would appreciate help from the community to establish what are the “healthy” practices:
-
Interfacing between Fortran
logicaland C++booltypeI want to interface to the following C++ class method (the class details are not relevant):
inline bool full() const { return count == capacity; }My first approach was to use the corresponding C
boolmacro, giving me the interface:bool nanoflann_KNNResultSet_full(KNNResultSet_t *rs);(The pointer
*rsis supposed to be an instance of the class I’m wrapping.)According to a thread on Stack Overflow, the size of the C++
booland the Cboolare potentially incompatible on some compilers or might depend upon the build process. This lead me to consider mapping the C++boolto the Cintin the intermediate C layer. In the Fortran wrapper I can then map the Cintback to the defaultlogicaltype using the following if clause:! The C header (internally maps the C `bool` to 0 or 1) ! int nanoflann_KNNResultSet_full(KNNResultSet_t *rs); ! Fortran mapping back to default logical kind if (nanoflann_KNNResultSet_full(rs) > 0) then result = .true. else result = .false end ifHas anyone encountered issues when interfacing between bools before? Is the mapping of C++
boolto a Cint(0,1) preferred over the mapping to the Cbool? I am also not a fan of having to carrylogical(c_bool)around in my Fortran layer. -
Correct way to wrap a C++ object into C
This issue is not related to Fortran per se. I was confused by the numerous different approaches to flatten a C++ object for consumption in C. The multiple threads on Stack Overflow and other resources contain somewhat contradicting information.
I tried following the approach used in symengine/cwrapper.h and symengine/cwrapper.cpp initially (@certik), but ran into memory alignment problems. Instead, I ended up using the approach demonstrated in this blog post. If I understand correctly, by casting the C++ objects into
void *we loss the type safety of C++. However, once I wrap the C layer back into Fortran I can reestablish the type safety. I was wondering if someone has some further tips and resources on this topic? The case study given in the book by Damian Rouson on producing the Fortran Trilinos wrapper, seems already a bit outdated. -
View into memory of a C++ object
In part of the
nanoflannlibrary, the user is supposed to pass an instance of astd::vector<std::pair<int,double>>to the constructor of a C++ class. This vector is then used internally as a dynamic storage container for index and distance pairs found during a radius search. The definition of the class is the following:template <typename _DistanceType, typename _IndexType = size_t> class RadiusResultSet { public: typedef _DistanceType DistanceType; typedef _IndexType IndexType; public: const DistanceType radius; std::vector<std::pair<IndexType, DistanceType>> &m_indices_dists; inline RadiusResultSet( DistanceType radius_, std::vector<std::pair<IndexType, DistanceType>> &indices_dists) : radius(radius_), m_indices_dists(indices_dists) { init(); } // ... }I was wondering if an array of
struct Pair { int idx; double pair};objects could be mapped to the memory of the C++std::vector<std::pair<int,double>>instance&m_indices_dists? I thought this might be a way to make this object interoperable with a fortran array of typetype, bind(c) :: pair integer(c_int) :: idx real(c_double) :: pair end typeSince I could not find sufficient information to determine if this works, I decided to take the safe (but wasteful) approach of copying the data from the C++ object to Fortran arrays I allocate in the C wrapper layer using the tools from
ISO_Fortran_binding.hheader file. The C prototype is thenvoid nanoflann_RadiusResultSet_getResultPairs(RadiusResultSet_t *rs, CFI_cdesc_t *idxs, CFI_cdesc_t *dists, int* stat);and the corresponding Fortran interface is
subroutine nanoflann_RadiusResultSet_getResultPairs(rs,idxs,dists,stat) & bind(c,name="nanoflann_RadiusResultSet_getResultPairs") use, intrinsic :: iso_c_binding, only: c_ptr, c_double, c_int type(c_ptr), intent(in), value :: rs integer(c_int), intent(inout), allocatable :: idxs(:) real(c_double), intent(inout), allocatable :: dists(:) integer(c_int), intent(out), optional :: stat end subroutineThis interface would be much simpler, had the C++ developers used two separate lists instead of a list of pairs as their storage container, i.e.:
inline RadiusResultSet( DistanceType radius_, std::vector<IndexType> &indices, std::vector<DistanceType> &dists) : ...In this case I could have easily recovered pointers to the underlying
std::vectordata using the methodsindices.data(),indices.size()(and analogously for thedistsvector), saving myself one copy in the Fortran layer.
I would appreciate any answers or comments!
If anyone has experience using tools such as shroud or swig-fortran, I would be happy to hear their opinion. Can these tools also wrap templated classes?
.
