Topic: gdk_pixbuf_rotate

Hello

With cairo /gtk / gdk /pixbuf one has only gdk_pixbuf_rotate_simple which allows for pixbuf rotations with a multiple of 90 degrees.
I indeed have the need to ratate at any arbitrary angle. Searching for a solution I found a c function that does this:
stackoverflow.com/questions/37520296/can-a-gdk-pixbuf-be-rotated-by-something-less-than-90-degrees
Consequently a wrote a f-c-interface that to my opinion should work.
the fortran and c-files compile correctly, however the build process exits with error:
==============================================================================
Generating Makefile... Okay
==============================================================================
Compiling .\gdk_pixbuf_rotate.c
Processing default resource
Generating hl_viewer_devel.exe
build\hl_viewer.o:hl_viewer.f90:(.text+0x248f): undefined reference to `rotate'
collect2.exe: error: ld returned 1 exit status
Error: Last command making (hl_viewer_devel.exe) returned a bad status
Error: Make execution terminated

* Failed *

Fortran source:
module gdk_pixbuf_rotate
  use iso_c_binding

  implicit none

  interface
      ! GdkPixbuf *rotate(GdkPixbuf *src,double radian,int full_size)
      function  rotate(src,radian,full_size) bind (c)
            use iso_c_binding
            type(c_ptr),value :: src
            type(c_ptr):: ret
            real(c_float),value:: radian
            integer(c_int),value :: full_size
            type(c_ptr):: rotate
        end function rotate
   end interface
end module gdk_pixbuf_rotate



module v_handlers
  use iso_c_binding

  use gdk_events
  use gdk_pixbuf_hl
  use gtk_draw_hl
  use gtk_sup
  use gtk_hl
  use gdk_pixbuf_rotate

  !********************************
  ! Gtk modules for hl_cairo_viewer.f90
  use cairo, only: cairo_status, cairo_status_to_string
  use gdk_pixbuf, only: gdk_pixbuf_get_height, gdk_pixbuf_get_width, &
                      & gdk_pixbuf_scale_simple, gdk_pixbuf_get_pixels, &
                      & gdk_pixbuf_add_alpha, gdk_pixbuf_rotate_simple
  use gdk_pixbuf_hl
  use gtk, only: gtk_combo_box_get_active, gtk_combo_box_set_active, &
       & gtk_container_add, gtk_main, gtk_main_quit, gtk_widget_set_sensitive, &
       & gtk_widget_show_all, gtk_init, TRUE, FALSE

  implicit none



  character(len=256), dimension(:), allocatable :: file_list
  integer(kind=c_int) :: current_file
  integer :: width = 800, height=1100;
  type(c_ptr) :: tl_window, view, prev1000, prev500, prev100, prev50, prev10, prev5, prev1, next1, next5, next10, &
  & next50, next100, next500, next1000, select
  real, dimension (:,:), allocatable :: img_gray
  real img_max, img_min




contains


subroutine delete_v (widget, gdata)  bind(c)
    type(c_ptr), value :: widget, gdata
     
    call gtk_main_quit

  end subroutine delete_v

  recursive subroutine show_image(widget, gdata)  bind(c)
    type(c_ptr), value :: widget, gdata
    character(kind=c_char), dimension(:,:,:), pointer :: pixel

    integer(kind=c_int), pointer :: istep
    integer(kind=c_int) :: nx, ny, nxe, nye, nch, i,j,fu, nrs
    type(c_ptr) :: pixbuf, pixbuf_scaled
    character(len=120) :: errm=''
    real(kind=8) :: rx, ry, r;
    integer(kind=1):: red, green, blue

    if (.not. c_associated(view)) return

    if (c_associated(gdata)) then
       call c_f_pointer(gdata, istep)
       current_file = current_file + istep
       call gtk_combo_box_set_active(select, current_file)
    else
       current_file = gtk_combo_box_get_active(widget)
       if (current_file < 0) return
    end if

    call gtk_widget_set_sensitive(prev1, f_c_logical(current_file > 0))
    call gtk_widget_set_sensitive(prev5, f_c_logical(current_file > 4))
    call gtk_widget_set_sensitive(prev10, f_c_logical(current_file > 9))
    call gtk_widget_set_sensitive(prev50, f_c_logical(current_file > 49))
    call gtk_widget_set_sensitive(prev100, f_c_logical(current_file > 99))
    call gtk_widget_set_sensitive(prev500, f_c_logical(current_file > 499))
    call gtk_widget_set_sensitive(prev1000, f_c_logical(current_file > 999))
    call gtk_widget_set_sensitive(next1, f_c_logical(current_file < size(file_list)-1))
    call gtk_widget_set_sensitive(next5, f_c_logical(current_file < size(file_list)-5))
    call gtk_widget_set_sensitive(next10, f_c_logical(current_file < size(file_list)-10))
    call gtk_widget_set_sensitive(next50, f_c_logical(current_file < size(file_list)-50))
    call gtk_widget_set_sensitive(next100, f_c_logical(current_file < size(file_list)-100))
    call gtk_widget_set_sensitive(next500, f_c_logical(current_file < size(file_list)-500))
    call gtk_widget_set_sensitive(next1000, f_c_logical(current_file < size(file_list)-1000))

    errm = ''
    pixbuf = hl_gdk_pixbuf_new(trim(file_list(current_file+1))//c_null_char, &
         & error=errm)
    nch = gdk_pixbuf_get_n_channels(pixbuf)
    nx = gdk_pixbuf_get_width(pixbuf)
    ny = gdk_pixbuf_get_height(pixbuf)
    nrs = gdk_pixbuf_get_rowstride(pixbuf)
    if(nch.eq.3) then
        pixbuf =  gdk_pixbuf_add_alpha(pixbuf,FALSE,red,green,blue)
        nch = gdk_pixbuf_get_n_channels(pixbuf)
    endif
!    open(newunit=fu,action='write',file='test.txt', status='replace')
!    write(fu,*) 'nx:',nx
!    write(fu,*) 'ny:',ny
!    write(fu,*) '#  channels:',nch
!    write(fu,*) 'rowstride:',nrs
!    close(fU)
!   
    !call execute_command_line('notepad test.txt')

    allocate ( img_gray(nx,ny) ) 
    call c_f_pointer(gdk_pixbuf_get_pixels(pixbuf), pixel, int((/nch, nx, ny/)))
    img_min = 10e10; img_max = -10e10;
    do i=1,nx
      do j=1,ny
         img_gray(i,j) = 0.3d0*ichar(pixel(1,i,j)) + 0.59d0*ichar(pixel(2,i,j)) + &
         & 0.11d0 * ichar(pixel(3,i,j))
         if(img_gray(i,j) < img_min) img_min = img_gray(i,j)
         if(img_gray(i,j) > img_max) img_max = img_gray(i,j)
      end do
    end do
    do i=1,nx
      do j=1,ny
         pixel(1,i,j) = char(int(img_gray(i,j),kind=1));
         pixel(2,i,j) = char(int(img_gray(i,j),kind=1));
         pixel(3,i,j) = char(int(img_gray(i,j),kind=1));
         pixel(4,i,j) = char(255);
      end do
    end do
   
    deallocate(img_gray)
     
    pixbuf =  rotate(pixbuf,0.1,1)
    !pixbuf =  gdk_pixbuf_rotate_simple(pixbuf,90)

    nch = gdk_pixbuf_get_n_channels(pixbuf)
    nx = gdk_pixbuf_get_width(pixbuf)
    ny = gdk_pixbuf_get_height(pixbuf)
    nrs = gdk_pixbuf_get_rowstride(pixbuf)
    if(nch.eq.3) then
        pixbuf =  gdk_pixbuf_add_alpha(pixbuf,FALSE,red,green,blue)
        nch = gdk_pixbuf_get_n_channels(pixbuf)
    endif
   

    if (errm /= "") then
       write(error_unit, "(2A)") "Failed to open: ", &
            & trim(file_list(current_file+1))
       write(error_unit, "(2A)") "        ", trim(errm)
    else
       rx = real(nx)/real(width); ry = real(ny)/real(height);
       r = rx;
       nxe = nx; nye = ny;
       if (ry > 1.d0 .or. rx >1.d0) then
          if(ry .gt. rx) then
              r = ry
          endif
          nxe = int(real(nx)/r)
          nye = int(real(ny)/r)
       endif
           
       pixbuf_scaled = gdk_pixbuf_scale_simple(pixbuf,nxe,nye,1)

       !call hl_gtk_drawing_area_resize(view, [nxe, nye])
       call hl_gtk_drawing_area_draw_pixbuf(view, pixbuf_scaled)
    end if
  end subroutine show_image

  subroutine add_files(widget, gdata)  bind(c)
    type(c_ptr), value :: widget, gdata

    character(len=256), dimension(:), allocatable :: new_files, tmp
    logical, pointer :: idelete
    integer(kind=c_int) :: ipick, i

    ipick = hl_gtk_file_chooser_show(new_files, create=FALSE, &
         & initial_dir = "D:\Dropbox\Fourier_precompensation\FFT_2D_Landolt\Fortran", &
         & initial_file= "D:\Dropbox\Fourier_precompensation\FFT_2D_Landolt\Fortran\Email_Screenshot_160621-----de-blurred.tif",  &
         & multiple=TRUE, all=TRUE)

    if (.not. c_f_logical(ipick)) return

    call c_f_pointer(gdata, idelete)

    if (idelete) then
       if (allocated(file_list)) deallocate(file_list)
       allocate(file_list(size(new_files)))
       file_list(:) = new_files(:)
       call hl_gtk_combo_box_delete(select)

    else
       allocate(tmp(size(file_list)))
       tmp(:) = file_list(:)
       if (allocated(file_list)) deallocate(file_list)
       allocate(file_list(size(tmp)+size(new_files)))
       file_list(:size(tmp)) = tmp(:)
       file_list(size(tmp)+1:) = new_files(:)
       if (current_file < 0) current_file = 0
    end if

    do i = 1, size(new_files)
       call hl_gtk_combo_box_add_text(select, trim(new_files(i))//c_null_char)
    end do

    if (current_file < 0 .and. size(file_list) > 0) current_file = 0
    call gtk_combo_box_set_active(select, current_file)
    call gtk_widget_set_sensitive(select, f_c_logical(size(file_list)>0))
  end subroutine add_files

  subroutine red_channel(widget, gdata)  bind(c)
    type(c_ptr), value :: widget, gdata

    character(len=256), dimension(:), allocatable :: new_files, tmp
    logical, pointer :: idelete
    integer(kind=c_int) :: ipick, i

  end subroutine red_channel
end module v_handlers


program hl_cairo_viewer
  ! A very simple image viewer
  use gdk_pixbuf_rotate
  use v_handlers
  use iso_c_binding

  implicit none
  integer(kind=c_int) :: nfiles, i, istat
  integer(kind=c_int), dimension(14), target :: direction = [-1000,-500,-100,-50,-10,-5,-1, 1, 5, 10, 50, 100, 500, 1000]
  logical, dimension(2), target :: iremove = [.false., .true.]

  type(c_ptr) :: scroll, base, jb,jb0, junk, cmsg
  character(len=120) :: err_msg


  call chdir("D:\Dropbox\Fourier_precompensation\FFT_2D_Landolt\Fortran")
 
  call gtk_init()

  nfiles = command_argument_count()
  if (nfiles > 0) then
     allocate(file_list(nfiles))
     do i = 1, nfiles
        call get_command_argument(i, value=file_list(i))
     end do
     current_file = 0
  else
     current_file = -1
  end if

  tl_window = hl_gtk_window_new("Simple Image Viewer modified by REJ"//c_null_char, &
       & destroy=c_funloc(delete_v), resizable=TRUE)

  base = hl_gtk_box_new()
  call gtk_container_add(tl_window, base)

  view = hl_gtk_drawing_area_new(scroll=scroll, ssize=[width, height], &
       & has_alpha=TRUE, cairo_status=istat)
  if (istat /= 0) then
     cmsg = cairo_status_to_string(istat)
     call c_f_string(cmsg, err_msg)
     write(error_unit, "(2a)") "hl_cairo_viewer: ", trim(err_msg)
     stop
  end if

  call hl_gtk_box_pack(base, scroll)

  jb = hl_gtk_box_new(horizontal=TRUE)
  jb0 = hl_gtk_box_new(horizontal=TRUE)
  call hl_gtk_box_pack(base, jb0)
  call hl_gtk_box_pack(base, jb)

  prev1000 = hl_gtk_button_new("<-1000"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(1)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev1000, expand=FALSE)
  prev500 = hl_gtk_button_new("<-500"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(2)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev500, expand=FALSE)
  prev100 = hl_gtk_button_new("<-100"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(3)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev100, expand=FALSE)
  prev50 = hl_gtk_button_new("<-50"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(4)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev50, expand=FALSE)
  prev10 = hl_gtk_button_new("<-10"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(5)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev10, expand=FALSE)
  prev5 = hl_gtk_button_new("<-5"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(6)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, prev5, expand=FALSE)
  prev1 = hl_gtk_button_new("<-1"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(7)), &
       & tooltip="Go to the previous image."//c_null_char,&
       & sensitive=false)
  call hl_gtk_box_pack(jb, prev1, expand=FALSE)
  !call hl_gtk_box_pack(jb0, prev1, expand=FALSE)

  select = hl_gtk_combo_box_new(changed=c_funloc(show_image), &
       & sensitive=f_c_logical(nfiles > 0), tooltip=&
       & "Select an image to show"//c_null_char)
  !call hl_gtk_box_pack(jb, select, expand=TRUE)
  call hl_gtk_box_pack(jb0, select, expand=TRUE)

  next1 = hl_gtk_button_new("1->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(8)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, next1, expand=FALSE)

  next5 = hl_gtk_button_new("5->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(9)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles >=5))
  call hl_gtk_box_pack(jb, next5, expand=FALSE)

  next10 = hl_gtk_button_new("10->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(10)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles >= 10))
  call hl_gtk_box_pack(jb, next10, expand=FALSE)

  next50 = hl_gtk_button_new("50->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(11)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles >=50))
  call hl_gtk_box_pack(jb, next50, expand=FALSE)

  next100 = hl_gtk_button_new("100->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(12)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles >= 100))
  call hl_gtk_box_pack(jb, next100, expand=FALSE)

  next500 = hl_gtk_button_new("500->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(13)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles >=500))
  call hl_gtk_box_pack(jb, next500, expand=FALSE)

  next1000 = hl_gtk_button_new("1000->"//c_null_char, &
       & clicked=c_funloc(show_image), data=c_loc(direction(14)), &
       & tooltip="Go to the next image."//c_null_char, &
       & sensitive=f_c_logical(nfiles > 0))
  call hl_gtk_box_pack(jb, next1000, expand=FALSE)

  if (nfiles > 0) then
     do i = 1, nfiles
        call hl_gtk_combo_box_add_text(select, &
             & trim(file_list(i))//c_null_char)
     end do
  end if

  junk = hl_gtk_button_new("red channel"//c_null_char, &
       & clicked=c_funloc(red_channel), data=c_loc(iremove(1)), &
       & tooltip="Show red channel only."//c_null_char)
  call hl_gtk_box_pack(jb0, junk, expand=FALSE)

  junk = hl_gtk_button_new("Add files"//c_null_char, &
       & clicked=c_funloc(add_files), data=c_loc(iremove(1)), &
       & tooltip="Pick files to add to the list."//c_null_char)
  call hl_gtk_box_pack(jb0, junk, expand=FALSE)

  junk = hl_gtk_button_new("Replace files"//c_null_char, &
       & clicked=c_funloc(add_files), data=c_loc(iremove(2)), &
       & tooltip="Pick files to replace the list."//c_null_char)
!  call hl_gtk_box_pack(jb0, junk)
  call hl_gtk_box_pack(jb0, junk, expand=FALSE)

  junk=hl_gtk_button_new("Quit"//c_null_char, &
       & clicked=c_funloc(delete_v), tooltip=&
       & "Quit the viewer."//c_null_char)
  call hl_gtk_box_pack(jb0, junk, expand=FALSE)

  call gtk_widget_show_all(tl_window)
  if (nfiles == 0) call add_files(c_null_ptr, c_loc(iremove(2)))
     
  if (current_file >= 0) call gtk_combo_box_set_active(select, current_file)
  call gtk_main()

end program hl_cairo_viewer

c-source:
#include <gtk/gtk.h>
#include <math.h>

/* There are two reasonable sizes for a rotated image-- Either the minimum */
/*  bounding box which contains all rotated pixels (and a bunch of white space)*/
/*  or the maximum rectangle where all pixels come from the source image (but */
/*  where we lose some of the corners) */
/* The first is easy to calculate: The minimum bounding box will have the corners */
/*  of the rotated image on its edges, this leaves us with four triangles in */
/*  the corners of the bb. Two triangles have edges width*sin(theta), width*cos(theta) */
/*  and two have edges height*sin(theta), height*cos(theta) */
/*  so the new width height will be the sum of two adjacent triangle edges: */
/*   width" = width*cos + height*sin */
/*   height"= width*sin + height*cos */
/* Now for the maximum inscribed rectangle we draw a similar picture (except */
/*  the unknown rectangle is internal now) and get similar triangles. Here the*/
/*  equations are: */
/*   width = width'*cos + height'*sin */
/*   height= width'*sin + height'*cos */
/*  solving for height'... */
/*   height' = (width-width'*cos)/sin */
/*   height' = (height-width'*sin)/cos */
/*   (width-width'*cos)/sin = (height-width'*sin)/cos */
/*   width*cos - width'*cos^2 = height*sin - width'*sin^2 */
/*   width' * (sin^2-cos^2) = height*sin-width*cos */
/*   width' = (height*sin - width*cos)/(sin^2-cos^2) */
/*   height'= (width*sin - height*cos)/(sin^2-cos^2) */
/*  Note this produces garbage (0/0) when rotated by 45 degrees (135,225,...) */
/*   A little experimentation shows that at 45 degrees the only thing with */
/*   an internal rectangle is a square, all other aspect ratios have a height */
/*   of 0. A square, however, has an internal square with sides  1/sqrt(2) of the original */
/* When creating a full_size image (minimum bounding box) we should return */
/*  an image with an alpha channel (whether the original had one or no). */
/*  otherwise we should create an alpha channel only if the original had one */

/* A pixel at (x,y) will be rotated to: */
/*    ((x-width/2)*cos + (y-height/2)*sin + width'/2 ,                */
/*    =(x-width/2)*sin + (y-height/2)*cos + height'/2 )                */
/* A pixel at (x',y') will have come from: */
/*    ((x'-width'/2)*cos - (y'-height'/2)*sin + width/2 ,                */
/*     (x'-width'/2)*sin + (y'-height'/2)*cos + height/2 )                */


static GdkPixbuf *rotate(const GdkPixbuf *src,float radian,int full_size) {     
    double s = sin(radian), c = cos(radian);
    double as= s<0 ? -s : s, ac= c<0 ? -c : c;
    int width, height, nwidth, nheight;
    int hasalpha, nhasalpha;
    GdkPixbuf *ret;
    int nr,nc,r,col;
    double nmodr, nmodc;
    int alpha=0;
    guchar *pixels, *npixels, *pt, *npt;
    int rowstride, nrowstride, pixellen;
    if ( src==NULL )
        return( NULL );
    width     = gdk_pixbuf_get_width(src);
    height    = gdk_pixbuf_get_height(src);
    hasalpha  = gdk_pixbuf_get_has_alpha(src);
    rowstride = gdk_pixbuf_get_rowstride(src);
    pixels    = gdk_pixbuf_get_pixels(src);
    pixellen  = hasalpha ? 4 : 3;
    if ( full_size ==1) {
        nwidth = round( ac*width + as*height );
        nheight= round( as*width + ac*height );
        nhasalpha = TRUE;
    } else {
        double denom = as*as - ac*ac;
        if ( denom<.1e-7 && denom>-1.e-7 ) {
            if ( width!=height )
                return( NULL );
            nwidth = nheight = round( width/sqrt(2.0) );
        } else {
            nwidth = round( (height*as - width*ac)/denom );
            nheight = round( (width*as - height*ac)/denom );
        }
        if ( nwidth<=0 || nheight<=0 )
            return( NULL );
        nhasalpha = hasalpha;
    }
    ret = gdk_pixbuf_new(GDK_COLORSPACE_RGB,nhasalpha,8,nwidth,nheight);
    if ( ret==NULL )
        return( NULL );
    nrowstride = gdk_pixbuf_get_rowstride(ret);
    npixels    = gdk_pixbuf_get_pixels(ret);
    for ( nr=0; nr<nheight; ++nr ) {
        nmodr = nr-nheight/2.0;
        npt = npixels + nr*nrowstride;
        for ( nc=0; nc<nwidth; ++nc ) {
            nmodc = nc-nwidth/2.0;
            /* Where did this pixel come from? */
            r   = round( height/2 - nmodc*s + nmodr*c );
            col = round( width/2  + nmodc*c + nmodr*s );
            if ( r<0 || col<0 || r>=height || col>=width ) {
                alpha = 0;
                if ( r<0 ) r=0;
                else if ( r>=height ) r = height-1;
                if ( col<0 ) col = 0;
                else if ( col>=width ) col = width-1;
            } else
                alpha = 0xff;
            pt = pixels + r*rowstride + col*pixellen;
            *npt++ = *pt++;
            *npt++ = *pt++;
            *npt++ = *pt++;
            if ( hasalpha && alpha!=0 )
                alpha = *pt;
            if ( nhasalpha )
                *npt++ = alpha;       
        }
    }
   return( ret );
}

Project-File (make-file):
#
# Automagically generated by Approximatrix Simply Fortran 3.17
#
FC="C:\Program Files (x86)\Simply Fortran 3\mingw-w64\bin\gfortran.exe"
CC="C:\Program Files (x86)\Simply Fortran 3\mingw-w64\bin\gcc.exe"
AR="C:\Program Files (x86)\Simply Fortran 3\mingw-w64\bin\ar.exe"
WRC="C:\Program Files (x86)\Simply Fortran 3\mingw-w64\bin\windres.exe"
PRJTK="C:\Program Files (x86)\Simply Fortran 3\fwin\sfprjtk.exe"
RM=rm -f

IDIR=-IC:/Users/rjoos/AppData/Local/sfpm/32/include

LDIR=-LC:/PROGRA~2/SIMPLY~1/MINGW-~1/lib/ -LC:/Users/rjoos/AppData/Local/sfpm/32/lib


OPTFLAGS= -O3 -fgraphite-identity -floop-interchange -floop-strip-mine -floop-block -floop-parallelize-all

SPECIALFLAGS=-m32 $(IDIR)

RCFLAGS=-O coff -F pe-i386

PRJ_FFLAGS=

PRJ_CFLAGS=-mms-bitfields

PRJ_LFLAGS=-lplplotf95 -lplplotf95c -lplplot -lplplotcxx -lcsirocsa -lqsastime -lgtk-3-fortran -lgtk-3.dll -lgdk-3.dll -lgthread-2.0.dll -lgdi32 -lole32 -latk-1.0.dll -lgdk_pixbuf-2.0.dll -lpangowin32-1.0.dll -lpangoft2-1.0.dll -lpango-1.0.dll -lpangocairo-1.0.dll -lcairo.dll -lcairo-gobject.dll -lgobject-2.0.dll -lgmodule-2.0.dll -lglib-2.0.dll -lfontconfig.dll -lfreetype.dll -lpng15.dll -lz -lintl.dll -lcomdlg32

FFLAGS=$(SPECIALFLAGS) $(OPTFLAGS) $(PRJ_FFLAGS) -JD:/Dropbox/Fourier_precompensation/FFT_2D_Landolt/Fortran/modules

CFLAGS=$(SPECIALFLAGS) $(OPTFLAGS) $(PRJ_CFLAGS)


"build\gdk_pixbuf_rotate.o": ".\gdk_pixbuf_rotate.c"
    @echo Compiling .\gdk_pixbuf_rotate.c
    @$(CC) -c -o "build\gdk_pixbuf_rotate.o" $(CFLAGS) ".\gdk_pixbuf_rotate.c"

"build\hl_viewer.o": ".\hl_viewer.f90"
    @echo Compiling .\hl_viewer.f90
    @$(FC) -c -o "build\hl_viewer.o" $(FFLAGS) ".\hl_viewer.f90"
"modules\gdk_pixbuf_rotate.mod" "modules\v_handlers.mod" : "build\hl_viewer.o" .EXISTSONLY
    @echo Compiling .\hl_viewer.f90
    @$(FC) -c -o "build\hl_viewer.o" $(FFLAGS) ".\hl_viewer.f90"


"build\sf_default_resource.res": "build\sf_default_resource.rc" "./Mandelbrot.ICO"
    @echo Processing default resource
    @$(WRC) build\sf_default_resource.rc $(RCFLAGS) -o build\sf_default_resource.res

clean: .SYMBOLIC
    @echo Deleting build\gdk_pixbuf_rotate.o and related files
    @$(RM) "build\gdk_pixbuf_rotate.o"
    @echo Deleting build\hl_viewer.o and related files
    @$(RM) "build\hl_viewer.o" "modules\gdk_pixbuf_rotate.mod" "modules\gdk_pixbuf_rotate.smod" "modules\v_handlers.mod" "modules\v_handlers.smod"
    @echo Deleting build\julia_pixbuf_devel.o and related files
    @$(RM) "build\julia_pixbuf_devel.o"
    @echo Deleting build\mandelbrot_pixbuf_zoom_develop.o and related files
    @$(RM) "build\mandelbrot_pixbuf_zoom_develop.o"
    @echo Deleting build\rotate.o and related files
    @$(RM) "build\rotate.o"
    @echo Deleting default icon resource
    @$(RM) "build\sf_default_resource.res"
    @echo Deleting hl_viewer_devel.exe
    @$(RM) "hl_viewer_devel.exe"

"hl_viewer_devel.exe":  "build\gdk_pixbuf_rotate.o" "build\hl_viewer.o" "build\sf_default_resource.res" "build\Mandelbrot_develop_GTK3.prj.target"
    @echo Generating hl_viewer_devel.exe
    @$(FC) -o "hl_viewer_devel.exe" -static -m32 -mwindows "build\gdk_pixbuf_rotate.o" "build\hl_viewer.o" "build\sf_default_resource.res" $(LDIR) $(PRJ_LFLAGS)

all: "hl_viewer_devel.exe" .SYMBOLIC

Sorry, has got a long post. It would be nice if code could be added seperately.

Roland

Re: gdk_pixbuf_rotate

Roland,

The compiler is complaining that it can't find a function named rotate.  The link you provided showed a function named gdk_pixbuf_rotate.  Did you change the name?

Additionally, the link also defines the function as static, meaning it will not be available outside that particular C file.  You'll need to remove the static keyword to make sure it is visible.

Your interface to it is also slightly wrong.  The interface signature should be:

! GdkPixbuf *gdk_pixbuf_rotate(GdkPixbuf *src,double radian,gboolean full_size)
interface
    function rotate(src, radian, full_size) bind(c, name="gdk_pixbuf_rotate")
    use iso_c_binding
    implicit none
    type(c_ptr), value::src
    real(kind=c_double), value::radian
    logical(kind=c_bool), value::full_size
    type(c_ptr)::rotate
    end function rotate
end interface

You'll note that I used c_double for the radian argument.  You also don't need the ret argument in the interface as it isn't defined as part of the function signature.

Let me know if the above helps.

Jeff Armstrong
Approximatrix, LLC

Re: gdk_pixbuf_rotate

Jeff,
Thanks. Yes, I renamed the c-function and changed the interface slightly because it was not clear how to translate gboolean to fortran.
Removing the property "static" essentially solved the problem.
Unfortunately the c-function didn't work properly and I implemented the function in fortran.
Roland