Git Product home page Git Product logo

Comments (6)

certik avatar certik commented on July 18, 2024

Thanks for the bug report. It will have to be debugged. I don't have Windows to help unfortunately.

from symengine.f90.

rikardn avatar rikardn commented on July 18, 2024

Thanks for testing to build on Windows. So far we have only tested this on Linux and MacOS on github actions.

Some assorted thoughts:
Is symengine-9.dll the c++ library? There seems to be a read at a strange location. This could be the number -1. Do you know if the c++ library works? Could you try compiling with gfortran?

from symengine.f90.

davidpfister avatar davidpfister commented on July 18, 2024

I can help with the testing on Windows, but my c++ skills are limited.
@rikardn, indeed, symengine-0.9.dll is the c++ library compiled with vcpkg. Location is strange because, since it is only used at runtime I need to place it in my output folder.
The library seems to work fine. For instance I can enter it when debugging
image

While looking into the interface, I noticed something

integer(c_size_t) function c_strlen(string) bind(C, name='strlen')
        import :: c_size_t, c_ptr
        type(c_ptr), intent(in), value :: string
    end function c_strlen

strlen already caused me some issues on Windows. I usually replace it with

integer function cstrlen(n, carray) result(res)
        integer, intent(in) :: n
        character(kind=c_char), intent(in) :: carray(*)
        integer :: ii

        do ii = 1, n
          if (carray(ii) == c_null_char) then
            res = ii - 1
            return
          end if
        end do
        res = ii
    end function

It looks like the problem are coming from the heap management
image

from symengine.f90.

davidpfister avatar davidpfister commented on July 18, 2024

@rikardn, I had the occasion to play with the fortran wrapper a little bit. I started by updating symengine to version 0.11 but that did not change anything.
I noticed something though, it seems that the culprit is the overload of the assignment:

subroutine basic_assign(a, b)
    class(basic), intent(inout) :: a
    class(basic), intent(in) :: b
    integer(c_long) :: exception
    if (.not. c_associated(a%ptr)) then
        a%ptr = c_basic_new_heap()
    end if
    exception = c_basic_assign(a%ptr, b%ptr)
    call handle_exception(exception)
    if (b%tmp) then
        call basic_free(b)
    end if
end subroutine

in that sub, b is intent(in) by default and as such it cannot be modified. The problem is that when calling basic_free(b) you change the value of b%ptr and this causes the problem reported earlier.

from symengine.f90.

rikardn avatar rikardn commented on July 18, 2024

Good catch! I think you are right. If I remember correctly the tmp attribute is used for a temporary right hand side expression for example in a = 2 * b where the 2 * b needs to be created, but directly freed in the assignment.

So in conclusion:

  1. We should change the intent of b to intent(inout)
  2. We should perphaps also use a Fortran implementation of strlen to not directly rely on the libc

from symengine.f90.

davidpfister avatar davidpfister commented on July 18, 2024

Hi @rikardn,
That's correct, the rhs is freed right after the assignment. However, not sure your first point is doable. At least ifort imposes that the second argument of the assignment is intent(in).
I tried something different:

  • in the constructors (let's say integer_new()) I declared the res as allocatable. By doing so, it gets automatically deallocated when exiting the scope and the final sub gets called.
    I think the %tmp becomes unnecessary, one has 'just' to define return values as allocatables and the final naturally does the rest.

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.