Feq-parse Updates - Evaluation with arrays now supported!

Summary
For those who are new to feq-parse, this package allows users to define functions as character strings and evaluate them on-the-fly. In earlier versions of feq-parse, only scalar inputs were accepted to the evaluate methods. When working with Fortran arrays, this required a do-loop around the evaluate call which would re-evaluate the parser objects each time; this is slow! The latest updates on the master branch allow for you to pass 1-D arrays to the evaluate methods, which provides significantly improved performance for evaluation of functions on arrays of independent variables. In a simple example, evaluating a gaussian on 10 million points, we show ~30x speedup with this new feature.

While implementing this new feature, Iā€™ve also added to the test suite and started tracking code coverage (weā€™re hitting 92% coverage as of today!), which is now noted in the README. From here, I am working on adding support for higher dimension arrays and will then work on GPU accelerated back-ends for the supported operator and function evaluations for even faster equation evaluation!

Scalar v. Array performance
As an example, consider the following program, where we set up an equation parser object and evaluate it at 10 million points by calling the evaluate method for each point; this is how we had to do equation evaluations with earlier versions of feq-parse.

program array_with_scalar_eval

  use FEQParse

  implicit none
  integer,parameter :: N = 10000000
  type(EquationParser) :: f
  character(LEN=1),dimension(1) :: independentVars
  character(LEN=30) :: eqChar
  real :: x(1)
  real :: feval(1:N)
  integer :: i
  real :: t1,t2

  ! Specify the independent variables
  independentVars = (/'x'/)

  ! Specify an equation string that we want to evaluate
  eqChar = 'f = \exp( -(x^2) )'

  ! Create the EquationParser object
  f = EquationParser(eqChar,independentVars)

  ! Evaluate the equation
  call cpu_time(t1)
  do i = 1,N
    x(1) = -1.0_real32 + (2.0_real32)/real(N,real32)*real(i - 1,real32)
    feval(i) = f % evaluate(x)
  end do
  call cpu_time(t2)
  print *, "runtime :", (t2 - t1)," s"

  ! Clean up memory
  call f % Destruct()

end program array_with_scalar_eval

Compiling and running this example (with gfortran 11.4.0) gives a runtime for the main loop as ~8.1 s

./array_with_scalar_eval 
 runtime :   8.11188793      s

With the updated version of feq-parse, we can instead pre-load an array for all of the values of x and call the evaluate method once. This example is shown below.

program array_with_array_eval

  use FEQParse

  implicit none
  integer,parameter :: N = 10000000
  type(EquationParser) :: f
  character(LEN=1),dimension(1) :: independentVars
  character(LEN=30) :: eqChar
  real :: x(1:N,1)
  real :: feval(1:N)
  integer :: i
  real :: t1,t2

  ! Specify the independent variables
  independentVars = (/'x'/)

  ! Specify an equation string that we want to evaluate
  eqChar = 'f = \exp( -(x^2) )'

  ! Create the EquationParser object
  f = EquationParser(eqChar,independentVars)

  ! Evaluate the equation
  call cpu_time(t1)
  do i = 1,N
    x(i,1) = -1.0_real32 + (2.0_real32)/real(N,real32)*real(i - 1,real32)
  end do
  feval = f % evaluate(x)
  call cpu_time(t2)
  print *, "runtime :", (t2 - t1)," s"

  ! Clean up memory
  call f % Destruct()

end program array_with_array_eval

Compiling and running this example (with the same compiler and on the same system) gives a runtime of ~0.27 s ( ~30x speedup )

./array_with_array_eval 
 runtime :  0.270846009      s
15 Likes

It looks great.

Note that there is a little bug in the tests:

$ fpm test
test.f90                               failed.
[  1%] Compiling...
test/test.f90:76:24:

   76 | end program testinclude "abs_r1fp32.f90"
      |                        1
Error: Expected label ā€˜testā€™ for END PROGRAM statement at (1)
compilation terminated due to -fmax-errors=1.
<ERROR> Compilation failed for object " test_test.f90.o "
<ERROR> stopping due to failed compilation
STOP 1
vmagnin@PC2:/tmp/feq-parse$ fpm run
<INFO> No executables to run
STOP 0

There is indeed an include command that was accidentally pasted line 76. The tests run OK after fixing it.

And maybe you could include the example of the README.md in a example/ directory, so that it could be launched with fpm run --example. And auto-examples = true in the manifest.

Iā€™ll add the fpm tests to the CI suite. At the moment, Iā€™m only testing with ctest

Examples have been added in the example/ subdirectory and the fpm.toml has been updated to include these examples. Additionally, a test has been added to install, test, and run examples with fpm. Thanks for the feedback @vmagnin !

1 Like

@fluidnumerics_joe , I have successfully run the tests and the three examples. The interest of the example directory is that lazy people like me can immediately start playing with the library by modifying these codes.

1 Like

Excellent! As I work up features, Iā€™ll keep it in mind to add to the examples.

1 Like

Looking into the implementation, I was wondering if the evaluate function could be made elemental? From the top of my head, I canā€™t recall if there are any rules against making member methods elemental.

Another thought I had was, which methods of the equation parser (if any) are overridable, and would this make it possible to implement custom operators?

  TYPE EquationParser
! ...
    CONTAINS

      PROCEDURE :: Destruct => Destruct_EquationParser
      PROCEDURE :: CleanEquation
      PROCEDURE :: Tokenize
      PROCEDURE :: ConvertToPostfix

      GENERIC :: Evaluate => Evaluate_sfp32, Evaluate_sfp64, &
                             Evaluate_r1fp32, Evaluate_r1fp64
      PROCEDURE, PRIVATE :: Evaluate_sfp32, Evaluate_sfp64
      PROCEDURE, PRIVATE :: Evaluate_r1fp32, Evaluate_r1fp64

      PROCEDURE :: Print_InFixTokens
      PROCEDURE :: Print_PostFixTokens

      procedure, private :: Priority

  END TYPE EquationParser

  INTERFACE EquationParser
    PROCEDURE Construct_EquationParser
  END INTERFACE EquationParser

For example, could I implement a (custom) calculus on top of this?

eqChar = "f = div( D * grad(u))'"

The Dedalus spectral solver (in Python) has something like this.

2 Likes

The issue with using an elemental for the evaluate generic ( I think ) is that this procedure calls Push for various ā€œfloat stacksā€ (e.g. Scalar fp32 and Rank 1 fp32 ) and f_of_x for each type ( e.g. Scalar fp32 and Rank 1 fp32 ). Though upon writing this, I suppose the push and pop procedures for the float stacks could be elemental as well as the f_of_x, which could cut down on the number of lines of code significantly here. Having the generic evaluate will still be needed, given plans to support passing c_ptrā€™s in for evaluation on the GPU. At any rate, Iā€™ll kick off another branch and see if that would work.

At the moment, the available functions are hard coded in the construct method for the FEQParse_Functions class. Though I think we could add a class for user-defined functions that allows one to map a character to a procedure through a procedure pointer. Opened an issue here to explore this more ( Add support for user-defined functions Ā· Issue #10 Ā· FluidNumerics/feq-parse Ā· GitHub )

Thanks for the feedback!

Nice to see the developments for this package. I have not had an opportunity yet to use it in earnest, but I do have an application in mind. One thing, though, not criticism, just a remark: if you use it to evaluate an array, then all variables should be arrays, right? No possibilty to combine a scalar with an array? Something along these lines:

real :: a(100)
real :: b

...
expression = 'exp( -b * a)'
...
write(*,*) f%evaluate( x )

@Arjen - Correct. Input matches output in type, kind, and rank, aside from the extra dimension for input independent variables.

Iā€™m not sure I understand your example, though; what is x ? are b and a declared as independent variables for the parser ? The parser does support multiplication, addition, subtraction, and exponentiation of arrays with constantsā€¦ Iā€™d have to think about how to have ā€œvariableā€ scalars, though. Issue opened here - Mix input types, e.g. scalars with arrays Ā· Issue #11 Ā· FluidNumerics/feq-parse Ā· GitHub

Thanks for the feedback

Itā€™s been work just trying to find time to work on projects that are made freely available for anyone to use (paying customers always come first). If you havenā€™t already, give the repo a star on github, so that we can work toward getting development sponsored on open collective.

I wanted to cut some corners, so I only presented an abbreviation of an example.

I will try and experiment a bit, because the application I very vaguely have in mind, may require some ā€œintrospectionā€. I better try and assemble my requirements :slight_smile:

Okay, I had some time to build the library and one of the examples. It did not work ā€œout-of-the-hoxā€: I used Intel oneAPI Fortran and MS Visual Studio on WIndows. There were a bunch of build errors. I will report them in more detail later - in the github project.
One thing I am interested in is whether it is possbile to extract the variable names. Related: I see that an unregistered variable causes an error message, but is it possible to catch that?
Oh, I also found a few bugs: I extended the scalar example with an extra variable, registered that, but got the wrong answer. And changing the expression led to a series of warnings ā€œAttempt to pop from empty token stackā€. I will report on that in the github project as well.

1 Like

Iā€™ll add ifx as well as windows OS to the GitHub actions tests. If you can provide some feedback on what you did to get it to build, that would be helpful and could save some time.

Iā€™m certain itā€™s possible to catch unregistered variables. Iā€™ll likely add this to the CleanEquation step which will return an error code during construction for the end user to manage.

With regards to your error, a minimal reproducer is helpful here; we can add that to the examples or tests.

This is very helpful feedback! Thank you!

I have just added the example that was failing for me to the github project. The build issue will come later, that requires a more detailed description :slight_smile:

Thanks @vmagnin, @ivanpribec , and @arjen for the feedback. Because of your responses, I now have tests for gfortran-9 through gfortran-12 and the Intel OneAPI compilers set up, with testing on Ubuntu and Windows (gfortran only here at the moment). Checks on memory usage are also done with valgrind for debug builds.

Since the original post, we now have rank 1 through rank 4 arrays up and running. Additionally, we have a few new issues open to resolve bugs with the intel compilers and to look into some new features (e.g. overridable functions). Aside from addressing the bugs, Iā€™m planning on finishing out the
year on this repository with some documentation for developers and users, before tackling new features.

If you end up using this repository in another project, feel free to add a link back to your project in the feq-parse README . Also, give the repository a :star: on Github if you like it!

1 Like

I have described the build issues I had yesterday in a new ticket. By the looks of them solving ought to be easy. Note: I used yesterdayā€™s version.

1 Like

That is a super cool project. I am writing a scripting interpreted language myself, fully in Fortran, for astrophysical image processing. This library will be PERFECT for evaluation of arbitrary transformation on images. Amazing work!

1 Like

Glad youā€™ll find it useful! Let me know if you need any assistance - you can either open a new discussion about your project on the discourse or open an issue at the feq-parse repository!

Thanks again to everyone for the feedback. The master branch now has fixes in place for ifort and ifx compilers as well as builds for Windows with Visual Studio and CMake. Iā€™ve currently got an issue open for using the ifx compiler with fpm (even though it works fine with CMake); this issue is summarized here fpm test with `ifx` compiler fails Ā· Issue #16 Ā· FluidNumerics/feq-parse Ā· GitHub