Git Product home page Git Product logo

Comments (5)

certik avatar certik commented on July 18, 2024

Yes, down the road we should generate it automatically to ensure the interface is consistent with any (future) possible changes to the C API.

from symengine.f90.

ivan-pi avatar ivan-pi commented on July 18, 2024

Out of curiosity I pulled together the interface routines needed to run the following program:

module small_test

use symengine_cwrapper
use iso_c_binding

implicit none

contains

  function c_char_ptr_to_fstring(c_char_ptr) result(fc)
    type(c_ptr) :: c_char_ptr
    character(len=:,kind=c_char), allocatable :: fc
    character(len=1000,kind=c_char), pointer :: f_string
    
    if (.not. c_associated(c_char_ptr)) then
        fc = ""
    else
        call c_f_pointer(c_char_ptr,f_string)
        fc = f_string(1:index(f_string,c_null_char))
    end if
  end function

subroutine f(i)

  integer(c_long), intent(in) :: i

  type(c_ptr) :: s = c_null_ptr ! string

  type(c_ptr) :: x = c_null_ptr
  type(c_ptr) :: y = c_null_ptr
  type(c_ptr) :: e = c_null_ptr
  type(c_ptr) :: n = c_null_ptr

  type(c_ptr) :: exception = c_null_ptr

  print *, "Symengine version: "//c_char_ptr_to_fstring(symengine_version())

  call basic_new_stack(x)
  call basic_new_stack(y)
  call basic_new_stack(e)
  call basic_new_stack(n)

  exception = symbol_set(x,"x"//c_null_char)
  exception = symbol_set(y,"y"//c_null_char)

  exception = integer_set_si(n, i);
  exception = basic_mul(e, n, x);
  exception = basic_add(e, e, y);

  s = basic_str(e)
  print *, "Result: ", c_char_ptr_to_fstring(s)
  call basic_str_free(s)
  s = c_null_ptr

  print *, c_associated(s), c_char_ptr_to_fstring(s)

  call basic_free_stack(x)
  call basic_free_stack(y)
  call basic_free_stack(e)
  call basic_free_stack(n)

end subroutine

end module

program small_test_program

  use small_test
  use iso_c_binding
  implicit none

  call f(5_c_long)

end program

(Note: the symengine_wrapper module is not included because I have some mistakes left).

After figuring out all the libraries needed to install symengine, I was able to compile the example using:

gfortran -Wall -c symengine_cwrapper.f90
gfortran -Wall -c test_symengine.f90
gfortran -o test_symengine -I/usr/local/include/symengine symengine_cwrapper.o test_symengine.o -L/usr/local/lib -lsymengine -lteuchos -lstdc++ -lmpfr -lgmp -lbfd

And finally, the result of the program:

$ ./test_symengine
 Symengine version: 0.6.0
 Result: 5*x + y
 F

from symengine.f90.

certik avatar certik commented on July 18, 2024

from symengine.f90.

ivan-pi avatar ivan-pi commented on July 18, 2024

Could you point me to the files containing the C++ API in the original symengine repository?

Typically, the high-level Fortran API can be made very similar to the C++ one.

from symengine.f90.

certik avatar certik commented on July 18, 2024

Yes, the main C++ API is in this directory in the header files:

https://github.com/symengine/symengine/tree/master/symengine

For example the Mul class is here:

https://github.com/symengine/symengine/blob/9fc2716cab4a6d2d89a3f9d765a04ef1594c6bcf/symengine/mul.h

The best way to understand how to use it is from tests, e.g., here:

https://github.com/symengine/symengine/blob/9fc2716cab4a6d2d89a3f9d765a04ef1594c6bcf/symengine/tests/basic/test_arit.cpp

This is the main API used throughout SymEngine. Then there is a simpler higher level API here:

https://github.com/symengine/symengine/blob/9fc2716cab4a6d2d89a3f9d765a04ef1594c6bcf/symengine/expression.h
https://github.com/symengine/symengine/blob/9fc2716cab4a6d2d89a3f9d765a04ef1594c6bcf/symengine/tests/expression/test_expression.cpp

Which is just a thin wrapper to provide easier C++ interface, with a possible small performance hit.

For Fortran, I suggest we use the C interface, as it takes care of exceptions and other things, and we build whatever is the most natural in Fortran. If we can somehow overload operators in Fortran and not leak memory, that would be great.

from symengine.f90.

Related Issues (6)

Recommend Projects

  • React photo React

    A declarative, efficient, and flexible JavaScript library for building user interfaces.

  • Vue.js photo Vue.js

    🖖 Vue.js is a progressive, incrementally-adoptable JavaScript framework for building UI on the web.

  • Typescript photo Typescript

    TypeScript is a superset of JavaScript that compiles to clean JavaScript output.

  • TensorFlow photo TensorFlow

    An Open Source Machine Learning Framework for Everyone

  • Django photo Django

    The Web framework for perfectionists with deadlines.

  • D3 photo D3

    Bring data to life with SVG, Canvas and HTML. 📊📈🎉

Recommend Topics

  • javascript

    JavaScript (JS) is a lightweight interpreted programming language with first-class functions.

  • web

    Some thing interesting about web. New door for the world.

  • server

    A server is a program made to process requests and deliver data to clients.

  • Machine learning

    Machine learning is a way of modeling and interpreting data that allows a piece of software to respond intelligently.

  • Game

    Some thing interesting about game, make everyone happy.

Recommend Org

  • Facebook photo Facebook

    We are working to build community through open source technology. NB: members must have two-factor auth.

  • Microsoft photo Microsoft

    Open source projects and samples from Microsoft.

  • Google photo Google

    Google ❤️ Open Source for everyone.

  • D3 photo D3

    Data-Driven Documents codes.