Making computer graphics in Fortran without GUI (just creating a PNG)

Maybe you are frightened to use gtk-fortran (https://github.com/vmagnin/gtk-fortran/wiki) because building a GUI is not so easy. But do you know you can also make computer graphics in Fortran without any GUI, using the GdkPixbuf library included in GTK ? Simply talking, a pixbuf is a 1D array containing the RGB intensities of each pixel of the image. So pixel(1) is the red intensity (between 0 and 255) of the first pixel (top left), pixel(2) and pixel(3) its green and blue intensities, pixel(4) the red intensity of the next pixel on the same line, and so on. Lines are stored one after the other in the array.

Here is an example creating a PNG file of a colored Sierpinski triangle:

program pixbuf_without_gui
  use iso_c_binding, only: c_ptr, c_null_char, c_null_ptr, &
                         & c_f_pointer, c_char, c_int
  use gdk_pixbuf, only: gdk_pixbuf_get_n_channels, gdk_pixbuf_get_pixels, &
                      & gdk_pixbuf_get_rowstride, gdk_pixbuf_new
  use gtk, only: GDK_COLORSPACE_RGB, FALSE
  use gtk_os_dependent, only: gdk_pixbuf_savev

  implicit none
  type(c_ptr) :: my_pixbuf
  ! We use chars because we need unsigned integers:
  character(c_char), dimension(:), pointer :: pixel
  integer(c_int) :: nch, rowstride, pixwidth, pixheight
  integer(c_int) :: cstatus   ! Command status
  double precision, dimension(1:3) :: x, y
  double precision :: xx, yy, diag, r
  integer :: s            ! Triangle vertex number
  integer :: n = 300000   ! Number of points
  integer :: i, p

  ! We create a "pixbuffer" to store the pixels of the image.
  ! This pixbuffer has no Alpha channel (15% faster), only RGB.
  ! https://developer.gnome.org/gdk-pixbuf/stable/gdk-pixbuf-The-GdkPixbuf-Structure.html
  pixwidth  = 800
  pixheight = 800
  my_pixbuf = gdk_pixbuf_new(GDK_COLORSPACE_RGB, FALSE, 8_c_int, &
                           & pixwidth, pixheight)
  nch = gdk_pixbuf_get_n_channels(my_pixbuf)
  rowstride = gdk_pixbuf_get_rowstride(my_pixbuf)
  print *, "Channels= ", nch, "      Rowstride=", rowstride
  call c_f_pointer(gdk_pixbuf_get_pixels(my_pixbuf), pixel, &
                 & (/pixwidth*pixheight*nch/))

  ! The background is black (red=0, green=0, blue=0):
  pixel = char(0)
  ! Diagonal of the image:
  diag = sqrt(real(pixwidth*pixwidth + pixheight*pixheight, kind(0d0)))
  ! Coordinates of the triangle vertices:
  x = (/ pixwidth/2d0,  0d0,                      (pixwidth-1)*1d0        /)
  y = (/ 0d0,           pixheight*sqrt(3d0)/2d0,  pixheight*sqrt(3d0)/2d0 /)
  ! We start at an arbitrary position:
  xx = (x(1) + x(2)) / 2d0
  yy = (y(1) + y(2)) / 2d0

  do i = 1, n
      ! We choose randomly a vertex number (1, 2 or 3):
      call random_number(r)
      s = 1 + int(3*r)
      ! We compute the coordinates of the new point:
      xx = (xx + x(s)) / 2d0
      yy = (yy + y(s)) / 2d0
      ! Position of the corresponding pixel in the pixbuffer:
      p = 1 + nint(xx)*nch + nint(yy)*rowstride
      ! Red, Green, Blue values computed from the distances to vertices:
      pixel(p)   = char(int(255 * sqrt((xx-x(1))**2 + (yy-y(1))**2) / diag))
      pixel(p+1) = char(int(255 * sqrt((xx-x(2))**2 + (yy-y(2))**2) / diag))
      pixel(p+2) = char(int(255 * sqrt((xx-x(3))**2 + (yy-y(3))**2) / diag))
  end do

  ! Save the picture as a PNG:
  ! https://developer.gnome.org/gdk-pixbuf/stable/gdk-pixbuf-File-saving.html
  ! https://mail.gnome.org/archives/gtk-list/2004-October/msg00186.html
  cstatus = gdk_pixbuf_savev(my_pixbuf, "sierpinski_triangle.png"//c_null_char,&
              & "png"//c_null_char, c_null_ptr, c_null_ptr, c_null_ptr)
end program pixbuf_without_gui

If gtk-fortran is intalled, you compile and run the program:

$ gfortran pixbuf_without_gui.f90 $(pkg-config --cflags --libs gtk-3-fortran) && ./a.out
 Channels=            3       Rowstride=        2400

No window opens, but you will find a sierpinski_triangle.png file in the directory:

For more information, on the Sierpinski algorithm used, see:

8 Likes

The gtk-fortran modules contain Fortran / C interfaces. For example, this is the gdk_pixbuf_new() function called to create the pixbuffer:

! GDK_PIXBUF_AVAILABLE_IN_ALL
!GdkPixbuf *gdk_pixbuf_new (GdkColorspace colorspace, gboolean has_alpha, int bits_per_sample, int width, int height);
function gdk_pixbuf_new(colorspace, has_alpha, bits_per_sample, width, height)&
& bind(c)
  use iso_c_binding, only: c_ptr, c_int
  type(c_ptr) :: gdk_pixbuf_new
  integer(c_int), value :: colorspace
  integer(c_int), value :: has_alpha
  integer(c_int), value :: bits_per_sample
  integer(c_int), value :: width
  integer(c_int), value :: height
end function

In gtk-fortran, these interfaces are automatically generated by the cfwrapper.py python script, which parses the header files of the GTK libraries in /usr/include/.
The bind(c) statement means that this is an interface to a C function whose name will be the same as the Fortran function. As can be seen in the C prototype in comments, this function will return a C pointer, so we need the c_ptr type defined in the ISO_C_BINDING intrinsic module. The arguments are here all integers (including the gboolean type) and we use the c_int type. Note also that arguments must be passed by value, except C pointers (and arrays).

The GLib basic types are described here:
https://developer.gnome.org/glib/stable/glib-Basic-Types.html

The Sierpinski program given above is just a Fortran program which calls some C functions from the GdkPixbuf library to create a pixbuf array, then write values in that array (pixel is a Fortran pointer toward the C array, obtained with the c_f_pointer() function), and finally calls a C function to create the PNG file. Nor very simple, nor very complicated…

Thanks for the nice example! Perhaps I will try to adapt it to Newton fractals later.

Concerning the automatic interface generation using the cfwrapper.py python script; is it general enough to be used also for other C libraries?

1 Like

OK, let me know your progress if you try it.

Concerning the cfwrapper.py script, I would say it should be OK with other libraries based on the GLib. I have never used it with other libraries. It can perhaps give some good results, if the coding conventions are similar to those of the GLib/GTK libraries.

The wrapper scans all the header files of the library. It is mainly based on regular expressions, used first to clean the code from all things which can not be easily translated, then to transform the C prototypes and enums into their Fortran equivalent.

This is the core of the project and it has grown very (too) quickly at the beginning, and surely needs some code refactoring. I have begun refactoring peripheral features, but it is a delicate piece of software because of the regular expressions. Sometime when GTK or GLib are updated, some regex can need tuning because something new has appeared somewhere in the 700 header files (for example a new coding convention).

To follow the new guidelines concerning the licenses of our posts (Welcome to Discourse), I state that:

  • the code posted in the two first posts of that thread are under the same license as gtk-fortran (GNU GPL v3), being one of the examples of the project.
  • The text of those posts is under GNU Free Documentation License 1.3 (license of the gtk-fortran documentation).

I have just pushed a second tutorial based on the content of those posts:
Tutorial 2: drawing an image in a PNG file (without GUI)
https://github.com/vmagnin/gtk-fortran/wiki/Tutorial-2

1 Like

As I understand it, this doesn’t affect other posts, but only those that @vmagnin mentioned.

Unhappily, it seems old posts are not editable anymore. If an administrator can make them editable, I could modify them and replace the code by links toward GitHub.
And if deleting this post is necessary, it is not a problem for me.

Note that personally, I consider that the license applies to the program as a whole. If you copy for example the block which creates the pixbuf and the pixel array, it is quite generic code: there is not 36 ways to do that. Perhaps the only original thing in that part of the code is the variables names…

Note also that the GPL v3 acknowledges the rights of fair use. And probably, an author posting a little GPL v3 code of its own for educational purpose in Fortran-lang discourse is fair use.

1 Like
  • I am not a lawyer -

‘Viral’ is used to describe the behaviour with respect to derivative works. Threads replies (without the original code) cannot possibly be considered derivative work of the original post, much less the entire ‘archive of postings’ on the discourse.

Posts are typically self-contained and with a single author and so the site guidelines allow licenses to be applied on a post-by-post basis. The obvious exception is if you repost and modify code from elsewhere in which case you must retain the original license (like a repo fork).

Yes, ideally the license would be with the original post, and I’m not sure why you can’t edit it currently, however the burden of checking the license of third party code always lies with the person copying that code so there is no argument of ‘unwittingly’ copying.

2 Likes

I’ve now added a notice to the post indicating the appropriate licenses.
(I think this is preferable to allowing editing of very old posts and I’m happy to do this on request for any posts.)

3 Likes

Thank you very much Laurence!

3 Likes