Stdlib_system+plotting (?)

I was flexing with the newly added stdlib_system module to see if it can be used as a backend to enable using plotting libraries through piping.

For that I started from this reference Gnuplot | Programming in Modern Fortran and then adapted the example in the “Process” section to use run from stdlib_system. and got to the following (not-yet-working example):

program main
  implicit none
  integer,          parameter :: N       = 800       ! Number of values.
  real,             parameter :: XSTEP   = 0.1       ! Step size.

  integer :: i
  real    :: x(N), y(N)

  ! Generate plotting data.
  do i = 1, N
      x(i) = -30 + ((i - 1) * XSTEP)
      y(i) = sin(x(i) * 20) * atan(x(i))
  end do

  ! Plot the data as line chart.
  call plot(x, y, 'Gnuplot from Fortran')
contains
  subroutine plot(x, y, title)
      use stdlib_system
      use stdlib_strings, only: to_string
      use iso_c_binding
      !! Opens pipe to Gnuplot, writes Gnuplots settings, and plots
      type(process_type) :: p
      real,             intent(inout) :: x(:)  !! X values.
      real,             intent(inout) :: y(:)  !! Y values.
      character(len=*), intent(in)    :: title !! Plot and window title.

      character(len=80) :: buffer
      integer           :: i, rc
      character(len=80) :: args
      character(len=:), allocatable :: stdin

      args = "gnuplot -persist"//c_null_char

      !> settings
      stdin = 'reset session'//c_new_line
      stdin = stdin//'set terminal svg title "' // trim(title) // '"'//c_new_line
      stdin = stdin//'set title "' // trim(title) // '"'//c_new_line
      stdin = stdin//'set grid'//c_new_line
      stdin = stdin//'set nokey'//c_new_line//c_new_line
      ! Output X, Y data.
      stdin = stdin//'plot "-" using 1:2 with lines'//c_new_line 
      do i = 1, size(x)
          stdin = stdin//to_string(x(i), '(f12.8)')//' '//to_string(y(i), '(f12.8)')//c_new_line
      end do
      stdin = stdin//'e'//c_new_line

      ! End plot data.
      p = run(args, stdin=stdin)
      if (is_completed(p)) then
          print *, "Process completed successfully. The current directory: "
          print *, p%stdout
      else
          print *, "Process is still running (unexpected)."
      end if

  end subroutine plot

end program main

Running this program using fpm run from Windows or Linux through a WSL, I simply get gnuplot shell active on the terminal and I do see a temp file with a name signature inp_20250507_185254_0386219.tmp which is deleted when closing gnuplot in the console but no plot.

Any ideas what might be missing?

5 Likes

Since you are using the p%stdout here, you should change your run invocation to this

      p = run(args, stdin=stdin, want_stdout=.true.)

Also, no need to append c_null_char to the args since that is taken care of by the functions themselves whenever required. You could also consider making args an array of strings since that is supported too.

Another thing I noticed while trying to make your example work, The second line of stdin should be this

        stdin = stdin//'set terminal svg'//c_new_line
4 Likes

@suprit05 Brilliant!! thanks!!

Here the version that worked:

program main
  implicit none
  integer,          parameter :: N       = 800       ! Number of values.
  real,             parameter :: XSTEP   = 0.1       ! Step size.

  integer :: i
  real    :: x(N), y(N)

  ! Generate plotting data.
  do i = 1, N
      x(i) = -30 + ((i - 1) * XSTEP)
      y(i) = sin(x(i) * 20) * atan(x(i))
  end do

  ! Plot the data as line chart.
  call plot(x, y, 'Gnuplot from Fortran')
contains
  subroutine plot(x, y, title)
      use stdlib_system
      use stdlib_strings, only: to_string
      use iso_c_binding
      !! Opens pipe to Gnuplot, writes Gnuplots settings, and plots
      type(process_type) :: p
      real,             intent(inout) :: x(:)  !! X values.
      real,             intent(inout) :: y(:)  !! Y values.
      character(len=*), intent(in)    :: title !! Plot and window title.

      character(len=80) :: buffer
      integer           :: i, rc
      character(len=80) :: args
      character(len=:), allocatable :: stdin

      args = "gnuplot -persist "

      !> settings
      stdin = 'reset session'//c_new_line
      stdin = stdin//'set terminal window'//c_new_line
      stdin = stdin//'set title "' // trim(title) // '"'//c_new_line
      stdin = stdin//'set grid'//c_new_line
      stdin = stdin//'set nokey'//c_new_line//c_new_line
      ! Output X, Y data.
      stdin = stdin//'plot "-" using 1:2 with lines'//c_new_line 
      do i = 1, size(x)
          stdin = stdin//to_string(x(i), '(f12.8)')//' '//to_string(y(i), '(f12.8)')//c_new_line
      end do
      stdin = stdin//'e'//c_new_line

      ! End plot data.
      p = run(args, stdin=stdin, want_stdout=.true.)
      if (is_completed(p)) then
          print *, "Process completed successfully. The current directory: "
          print *, p%stdout
      else
          print *, "Process is still running (unexpected)."
      end if

  end subroutine plot

end program main

Notice that I changed here the terminal for: stdin = stdin//'set terminal window'//c_new_line

I knew that but I wasn’t sure if that was a necessary or useful thing to do here. What would you change here to make the use of an array of strings for the args?

6 Likes

Nice usage of stdlib’s subprocess module :clap: :clap: :clap:

2 Likes

Happy it worked, looks pretty good!

I do think it’s an overkill here but having seen quite a lot of API’s have their run signatures as

run ( program_name, args, ...)

where program_name would be "gnuplot" and args an array of arguments. Due to which, I like to pass the arguments as an array of strings. In this case, I would do it like this

        character(len=30), allocatable :: args(:)

        allocate (args(2))
        args(1) = "gnuplot"
        args(2) = "-persist"

        p = run(args, stdin=stdin, want_stdout=.true.)

Although I am not too familiar with all the caveats and fortran ways of dealing with array of strings, any enhancements would be appreciated.

This looks very interesting. Could be the starting point for a Fortran plotting framework. What do you think?

If I run the main program, nothing happens. All I get is:

❯ fpm run
Project is up to date
 Process completed successfully. The current directory:


I tried it on Arch Linux running Sway (which uses wayland). Did you try both Windows and Linux with your working example?

1 Like

I run arch too (with Hyprland) and the example does not work as it is, I changed set terminal window to set terminal x11, and that works and I see a small floating window.

Also, set terminal command in the gnuplot shell gives the list of all available terminals with your current installation

1 Like

Thank you, that did the trick!

“window” is not in the available terminals.
What might be even better is to not use set terminal at all. In my case gnuplot then uses the “qt” terminal by default.

1 Like

:innocent: you read my mind! This is what I had in mind and wanted to know if it was possible or not. The subprocess module that @FedericoPerini created is really a brilliant key step towards that!!

I would like to see a stdlib_plot module which would be a frontend giving a high-level API and which can sit atop plotting backends such as gnuplot, plotly, matplotlib (?). gnuplot can be a good starting point and default backend.

I’ve found this project GitHub - kookma/ogpf: ogpf is Object based interface to GnuPlot from Fortran 2003, 2008 and later to get quite close to the idea regarding the user experience. The Fortran API resembles enough matplotlib to make it quite easy to use. Using the subprocess approach would avoid the need of using intermediate files and I would vouch also for it being within stdlib or strongly depend on it to avoid code duplication and ecosystem fragmentation.

3 Likes