vmagnin / gtk-fortran

A GTK / Fortran binding. The documentation is in the Wiki tab.
GNU General Public License v3.0
251 stars 43 forks source link

Simple Menu Example #4

Closed bonanza closed 13 years ago

bonanza commented 13 years ago

I wrote a small example with a simple menu based on GtkUIManager:

! Copyright (C) 2011
! Free Software Foundation, Inc.

! This file is part of the gtk-fortran gtk+ Fortran Interface library.

! This is free software; you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation; either version 3, or (at your option)
! any later version.

! This software is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
! GNU General Public License for more details.

! Under Section 7 of GPL version 3, you are granted additional
! permissions described in the GCC Runtime Library Exception, version
! 3.1, as published by the Free Software Foundation.

! You should have received a copy of the GNU General Public License along with
! this program; see the files COPYING3 and COPYING.RUNTIME respectively.
! If not, see .
!
! gfortran -g gtk.f90 simplemenu.f90 `pkg-config --cflags --libs gtk+-2.0`
! Contributed by Jens Hunger

module handlers
  use gtk
  implicit none

  logical :: run_status = TRUE
  logical(c_bool) :: boolresult
  logical :: boolevent

  type(c_ptr) :: my_pixbuf
  character(c_char), dimension(:), pointer :: pixel
  integer :: nch, rowstride, width, height

contains
  ! User defined event handlers go here

! destroy all
  subroutine destroy (widget, gdata) bind(c)
    use iso_c_binding, only: c_ptr
    type(c_ptr), value :: widget, gdata
    print *, "my destroy"
    call gtk_main_quit ()
  end subroutine destroy

! delete event
  function delete_event (widget, event, gdata) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "my delete_event"
    ret = FALSE
  end function delete_event

! open file
  function file_open (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File open"
    ret = .false.
  end function file_open

! save file
  function file_save (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File save"
    ret = .false.
  end function file_save

! close file
  function file_close (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File close"
    ret = .false.
  end function file_close

! cut
  function cut (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Cut"
    ret = .false.
  end function cut

! copy
  function copy (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Copy"
    ret = .false.
  end function copy

! paste
  function paste (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Paste"
    ret = .false.
  end function paste

! help
  function help (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Help"
    ret = .false.
  end function help

  subroutine convert_c_string(textptr, f_string)
    use iso_c_binding, only: c_char
    implicit none
    character(c_char), dimension(:), pointer, intent(in) :: textptr
    character(len=*), intent(out) :: f_string
    integer :: i

    f_string=""
    i=1
    do while(textptr(i) .NE. char(0))
      f_string(i:i)=textptr(i)
      i=i+1
    end do
  end subroutine convert_c_string

end module handlers

program simplemenu

    use iso_c_binding
  use gtk
  use handlers

    implicit none

    type ui_action
        character(kind=c_char,len=30)::name
        character(kind=c_char,len=30)::label
        character(kind=c_char,len=30)::tooltip
        character(kind=c_char,len=30)::stock_id
        type(c_funptr)   ::c_handler
    end type ui_action

  type(c_ptr) :: mainwindow
  type(c_ptr) :: box
  type(c_ptr) :: menu_bar
  type(c_ptr) :: action_group,menu_manager,error
  character(c_char), dimension(:), pointer :: textptr
  character(len=512) :: error_string
  integer :: ui,i
  ! Menu action data
  type(ui_action),dimension(11)::action = (/&
    ui_action("FileMenuAction"//CNULL, "_File"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("OpenAction"//CNULL, "_Open"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("SaveAction"//CNULL, "_Save"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CloseAction"//CNULL, "_Close"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("QuitAction"//CNULL, "_Quit"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("EditMenuAction"//CNULL, "_Edit"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CutAction"//CNULL, "_Cut"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CopyAction"//CNULL, "_Copy"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("PasteAction"//CNULL, "_Paste"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("HelpMenuAction"//CNULL, "_Help"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("HelpAction"//CNULL, "_Help"//CNULL, CNULL, CNULL, c_null_funptr)&
    /)

  ! this is necessary because gfortran gives error:
  ! Function 'c_funloc' in initialization expression at must be an intrinsic function
  !action(1)%c_handler=c_funloc(destroy)
  action(2)%c_handler=c_funloc(file_open)
  action(3)%c_handler=c_funloc(file_save)
  action(4)%c_handler=c_funloc(file_close)
  action(5)%c_handler=c_funloc(destroy)
  !action(6)%c_handler=c_funloc(destroy)
  action(7)%c_handler=c_funloc(cut)
  action(8)%c_handler=c_funloc(copy)
  action(9)%c_handler=c_funloc(paste)
  !action(10)%c_handler=c_funloc(destroy)
  action(11)%c_handler=c_funloc(help)

    ! GTK initialisation            
  call gtk_init ()

  ! Properties of the main window :
  width = 700
  height = 700
  mainwindow = gtk_window_new (GTK_WINDOW_TOPLEVEL)
  call gtk_window_set_title(mainwindow, "Simple Menu Example"//CNULL)
  call gtk_window_set_default_size(mainwindow, 500, 500)

  ! Connect signals to the main window
  call g_signal_connect (mainwindow, "delete-event"//CNULL, c_funloc(delete_event))
  call g_signal_connect (mainwindow, "destroy"//CNULL, c_funloc(destroy))

  ! Fill action group with actions and connect signals
  action_group = gtk_action_group_new("Menu");
  do i=1,size(action)
      call gtk_action_group_add_action(action_group, gtk_action_new(action(i)%name,&
        action(i)%label,action(i)%tooltip,action(i)%stock_id))
      call g_signal_connect (gtk_action_group_get_action(action_group,action(i)%name),&
        "activate"//CNULL, action(i)%c_handler)
  enddo

  ! Insert action group into ui manager
  menu_manager = gtk_ui_manager_new ()
  call gtk_ui_manager_insert_action_group (menu_manager, action_group, 0)
  error = NULL
  ui = gtk_ui_manager_add_ui_from_file (menu_manager, "menu.xml"//CNULL, error)

  ! Handle error
  if (c_associated(error)) then
                call C_F_POINTER(error, textptr, (/512/))
                call convert_c_string(textptr, error_string)
                print *,"building menus failed: ", error_string
  endif

  ! Container for menu
  box = gtk_vbox_new (FALSE,0)
  call gtk_container_add (mainwindow, box)
  call gtk_box_pack_start (box, gtk_ui_manager_get_widget (menu_manager, "/MainMenu"//CNULL), FALSE, FALSE, 0)

  ! Show all
  call gtk_widget_show_all (mainwindow)

  ! Main loop
    call gtk_main ()

end program simplemenu

Here is the corresponding menu.xml with the XML representation of the menu:

vmagnin commented 13 years ago

Thank you very much Jens. This is an important new brick for our GUI ! For other users,it is obvious but important to note that the a.out executable file must be in the same directory as menu.xml ! (I first compile from the src directory !)

It works fine on my machines, even if I obtain this message in the terminal (3 times) when running, both with gfortran and g95: (a.out:3367): GLib-GObject-CRITICAL **: g_signal_connect_data: assertion `c_handler != NULL' failed

Do you obtain the same messages ? And Jerry also ?

I replaced call gtk_window_set_default_size(mainwindow, 500, 500) by the following line: call gtk_widget_set_size_request(mainwindow, 500, -1) It avoids having the menu in the middle of the window.

If you agree I will commit this example in the examples directory these next days.

bonanza commented 13 years ago

I added a comment that the executable must be in the same directory as menu.xml.

I also obtain the g_signal_connect_data warning, this is because the c_handler pointers for the menu headers are initialized with c_null_funptr in the action array initialization expression and never changed later. Unfortunately, the c_handlers cannot be initialized with their final values in the array initialization expression. However, I added some dummy function "menu" where the c_handlers of the menu headers point to. Now it works without any warnings.

Under Linux/Gnome I have the menu correctly aligned to the left side of the window with gtk_window_set_default_size(mainwindow, 500, 500), maybe the centering is some "MS Windows effect"? I replaced it by gtk_widget_set_size_request(mainwindow, 500, -1), which gives some strange layout with just window header+menu. Therefore I changed it to gtk_widget_set_size_request(mainwindow, 500, 500) in the current version.

Of course you can commit the example, that's for what it was made. And it's GPL'ed...

! Copyright (C) 2011
! Free Software Foundation, Inc.

! This file is part of the gtk-fortran gtk+ Fortran Interface library.

! This is free software; you can redistribute it and/or modify
! it under the terms of the GNU General Public License as published by
! the Free Software Foundation; either version 3, or (at your option)
! any later version.

! This software is distributed in the hope that it will be useful,
! but WITHOUT ANY WARRANTY; without even the implied warranty of
! MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
! GNU General Public License for more details.

! Under Section 7 of GPL version 3, you are granted additional
! permissions described in the GCC Runtime Library Exception, version
! 3.1, as published by the Free Software Foundation.

! You should have received a copy of the GNU General Public License along with
! this program; see the files COPYING3 and COPYING.RUNTIME respectively.
! If not, see .
!
! gfortran -g gtk.f90 simplemenu.f90 -o simplemenu `pkg-config --cflags --libs gtk+-2.0`
! menu.xml must be copied to the same directory as the simplemenu executable!               
! Contributed by Jens Hunger

module handlers
  use gtk
  implicit none

  logical :: run_status = TRUE
  logical(c_bool) :: boolresult
  logical :: boolevent

  type(c_ptr) :: my_pixbuf
  character(c_char), dimension(:), pointer :: pixel
  integer :: nch, rowstride, width, height

contains
  ! User defined event handlers go here

! destroy all
  subroutine destroy (widget, gdata) bind(c)
    use iso_c_binding, only: c_ptr
    type(c_ptr), value :: widget, gdata
    print *, "my destroy"
    call gtk_main_quit ()
  end subroutine destroy

! delete event
  function delete_event (widget, event, gdata) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "my delete_event"
    ret = FALSE
  end function delete_event

! open file
  function file_open (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File open"
    ret = .false.
  end function file_open

! save file
  function file_save (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File save"
    ret = .false.
  end function file_save

! close file
  function file_close (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "File close"
    ret = .false.
  end function file_close

! cut
  function cut (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Cut"
    ret = .false.
  end function cut

! copy
  function copy (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Copy"
    ret = .false.
  end function copy

! paste
  function paste (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Paste"
    ret = .false.
  end function paste

! help
  function help (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    print *, "Help"
    ret = .false.
  end function help

! menu dummy function
  function menu (widget, event, gdata ) result(ret)  bind(c)
    use iso_c_binding, only: c_ptr, c_int, c_bool
    logical(c_bool)    :: ret
    type(c_ptr), value :: widget, event, gdata
    !print *, "Menu"
    ret = .false.
  end function menu

  subroutine convert_c_string(textptr, f_string)
    use iso_c_binding, only: c_char
    implicit none
    character(c_char), dimension(:), pointer, intent(in) :: textptr
    character(len=*), intent(out) :: f_string
    integer :: i

    f_string=""
    i=1
    do while(textptr(i) .NE. char(0))
      f_string(i:i)=textptr(i)
      i=i+1
    end do
  end subroutine convert_c_string

end module handlers

program simplemenu

    use iso_c_binding
  use gtk
  use handlers

    implicit none

    type ui_action
        character(kind=c_char,len=30)::name
        character(kind=c_char,len=30)::label
        character(kind=c_char,len=30)::tooltip
        character(kind=c_char,len=30)::stock_id
        type(c_funptr)   ::c_handler
    end type ui_action

  type(c_ptr) :: mainwindow
  type(c_ptr) :: box
  type(c_ptr) :: menu_bar
  type(c_ptr) :: action_group,menu_manager,error
  character(c_char), dimension(:), pointer :: textptr
  character(len=512) :: error_string
  integer :: ui,i
  ! Menu action data
  type(ui_action),dimension(11)::action = (/&
    ui_action("FileMenuAction"//CNULL, "_File"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("OpenAction"//CNULL, "_Open"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("SaveAction"//CNULL, "_Save"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CloseAction"//CNULL, "_Close"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("QuitAction"//CNULL, "_Quit"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("EditMenuAction"//CNULL, "_Edit"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CutAction"//CNULL, "_Cut"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("CopyAction"//CNULL, "_Copy"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("PasteAction"//CNULL, "_Paste"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("HelpMenuAction"//CNULL, "_Help"//CNULL, CNULL, CNULL, c_null_funptr),&
    ui_action("HelpAction"//CNULL, "_Help"//CNULL, CNULL, CNULL, c_null_funptr)&
    /)

  ! this is necessary because gfortran gives error:
  ! Function 'c_funloc' in initialization expression at must be an intrinsic function
  ! and g95 e.g.:
  ! Variable 'destroy' cannot appear in an initialization expression
  action(1)%c_handler=c_funloc(menu)
  action(2)%c_handler=c_funloc(file_open)
  action(3)%c_handler=c_funloc(file_save)
  action(4)%c_handler=c_funloc(file_close)
  action(5)%c_handler=c_funloc(destroy)
  action(6)%c_handler=c_funloc(menu)
  action(7)%c_handler=c_funloc(cut)
  action(8)%c_handler=c_funloc(copy)
  action(9)%c_handler=c_funloc(paste)
  action(10)%c_handler=c_funloc(menu)
  action(11)%c_handler=c_funloc(help)

    ! GTK initialisation            
  call gtk_init ()

  ! Properties of the main window :
  width = 700
  height = 700
  mainwindow = gtk_window_new (GTK_WINDOW_TOPLEVEL)
  call gtk_window_set_title(mainwindow, "Simple Menu Example"//CNULL)
  call gtk_widget_set_size_request(mainwindow, 500, 500)

  ! Connect signals to the main window
  call g_signal_connect (mainwindow, "delete-event"//CNULL, c_funloc(delete_event))
  call g_signal_connect (mainwindow, "destroy"//CNULL, c_funloc(destroy))

  ! Fill action group with actions and connect signals
  action_group = gtk_action_group_new("Menu");
  do i=1,size(action)
      call gtk_action_group_add_action(action_group, gtk_action_new(action(i)%name,&
        action(i)%label,action(i)%tooltip,action(i)%stock_id))
      call g_signal_connect (gtk_action_group_get_action(action_group,action(i)%name),&
        "activate"//CNULL, action(i)%c_handler)
  enddo

  ! Insert action group into ui manager
  menu_manager = gtk_ui_manager_new ()
  call gtk_ui_manager_insert_action_group (menu_manager, action_group, 0)
  error = NULL
  ui = gtk_ui_manager_add_ui_from_file (menu_manager, "menu.xml"//CNULL, error)

  ! Handle error
  if (c_associated(error)) then
    call C_F_POINTER(error, textptr, (/512/))
    call convert_c_string(textptr, error_string)
    print *,"building menus failed: ", error_string
  endif

  ! Container for menu
  box = gtk_vbox_new (FALSE,0)
  call gtk_container_add (mainwindow, box)
  call gtk_box_pack_start (box, gtk_ui_manager_get_widget (menu_manager, "/MainMenu"//CNULL), FALSE, FALSE, 0)

  ! Show all
  call gtk_widget_show_all (mainwindow)

  ! Main loop
    call gtk_main ()

end program simplemenu
vmagnin commented 13 years ago

Fine ! I just commit menu.f90 and menu.xml. Concerning the gtk_window_set_default_size I am also working with Linux Ubuntu 10.10 (GTK+ 2.22). Yes, the menu is left aligned, but vertically it appears centered ! It is the same with gtk_widget_set_size_request(mainwindow, 500, 500). I put the gtk_widget_set_size_request(mainwindow, 500, -1) possibility in comment.

If you test other widgets, you can directly send your examples to vincent.magnin@libertysurf.fr

I am still working on the python script, which can now generate automatically the enumerations (typedef enum), except for Cairo by now. I think this first phase of the project will soon be over because I think we have now access to the majority of GTK widgets. The second phase will concentrate on testing and writing examples, and adding automatic tests.

bonanza commented 13 years ago

The differing vertical alignment behavior is really strange, on my system (Linux Mint 10, GTK+ 2.20) all looks like expected (?) top/left-aligned with gtk_widget_set_size_request(mainwindow, 500, 500) as well as gtk_window_set_default_size(mainwindow, 500, 500). Maybe a GtkAlignment widget should be used to get identical alignments on all systems?

vmagnin commented 13 years ago

Yes, strange. In the official doc, there is no difference between 2.20 and 2.22 for GtkVBox. Perhaps something has changed in the parents widgets... Concerning GtkAlignment I found that: "the desired effect can in most cases be achieved by using the "halign", "valign" and "margin" properties on the child widget, so GtkAlignment should not be used in new code."

"The "valign" property "valign" GtkAlign : Read / Write How to distribute vertical space if widget gets extra space, see GtkAlign Default value: GTK_ALIGN_FILL Since 3.0"

I will try menu.f90 with Windows 7 to see how it behaves...

vmagnin commented 13 years ago

Same little problem with Windows 7 and the DLLs of GIMP 2.6.11 (GTK+ 2.16 ?)

jerryd commented 13 years ago

Hi Folks, just catching up here. I have not been able to get this program to compile. I think I do not have the right version of gtk.f90. Vincent, did you push your commits so they actually go out to github? maybe i am having a bad day. :)

vmagnin commented 13 years ago

Hi Jerry, I commited 2 days ago in the devel branch the following files: menu.f90, menu.xml, gtk.f90, gtk-auto.f90, gtkenums-auto.f90 Tell me if you have still a problem. Vincent

bonanza commented 13 years ago

I tried with Windows XP/SP3 and G95: Now I see also the strange behavior. Obviously, the menu header is spread over the full height of the window body. I used the DLLs from http://www.gtk.org/download-windows.html (GLib 2.26.1, gdk-pixbuf 2.22.1, GTK+ 2.22.1, cairo 1.10.2, zlib 1.2.5)

bonanza commented 13 years ago

Windows XP/SP3 with gfortran (4.6.0 20110214 (experimental) [trunk revision 170140]) using the same GDK/GTK+ DLLs gives another behavior: Here the menu header is not spread, but vertically centered.

vmagnin commented 13 years ago

It is quite strange that it depends also on the compiler. Interesting... Jerry, have you an idea ? Anyway, waiting GTK+ 3, we can use GtkAlignment (or perhaps GtkTable): http://zetcode.com/tutorials/gtktutorial/gtklayoutmanagement/

jerryd commented 13 years ago

It could be we have the C interface wrong for one of these functions, maybe a pass by value vs not pass by value. The result could be strange behavior.

vmagnin commented 13 years ago

Perhaps a problem with gtk_box_pack_start or gtk_vbox_new, which uses gboolean ? In tests.f90, I wrote a test for the passing of gboolean from GTK to Fortran (logical (c_bool)). Perhaps a problem from Fortran to GTK ? In GTK doc, gboolean is gint, which is int. FALSE is the value 0. See the discussion about c_bool: http://groups.google.com/group/comp.lang.fortran/browse_thread/thread/3c2784c55d402ced/a3eed829339dc61b?lnk=gst&q=gboolean#a3eed829339dc61b

jerryd commented 13 years ago

This makes sense. There are known bool differences even between Intel ifort and gfortran. I will have to try to dig out the information on those.

vmagnin commented 13 years ago

I commited a new version of tests.f90. It includes some tests on gbooleans. It works fine for me. Can you please test it on your machines ?

jtappin commented 13 years ago

Could it be a 32/64 bit issue? I see the vertical centring on a 32-bit machine, but not on a 64 bit machine -- both running Linux and both using gfortran (slightly different snapshots, I think the 32 bit is 28 Feb and the 64 bit is 4 Mar or thereabouts). On both the current tests.f90 program reports no errors.

vmagnin commented 13 years ago

Interesting. My machines are also working with 32 bits systems. Bonanza, what type is your machine ?

bonanza commented 13 years ago

My Linux machine is working with 64 bit, Windows is working with 32 bit. I think, 32/64 bit issue sounds reasonable.

vmagnin commented 13 years ago

Yes, from the machines used by myself, jtappin and bonanza, we can reasonably conclude:

Probably the problem comes from: GtkWidget * gtk_vbox_new (gboolean homogeneous, gint spacing); or void gtk_box_pack_start (GtkBox box, GtkWidget child, gboolean expand, gboolean fill, guint padding);

A problem with gboolean ? => logical(c_bool) Can you try the following program and post the result ?

use iso_c_binding logical(c_bool), parameter :: TRUE = .true. logical(c_bool), parameter :: FALSE = .false. integer :: i

print , c_bool print , kind(.true.) print , TRUE print , FALSE

i = TRUE print , i i = FALSE print , i end

On my 32 bits machine with gfortran under linux, I obtain: 1

4

T

F

1

0

bonanza commented 13 years ago

Linux 64 bit, gfortran:

compilation: i = TRUE 1 Warning: Extension: Conversion from LOGICAL(1) to INTEGER(4) at (1)

i = FALSE
1
Warning: Extension: Conversion from LOGICAL(1) to INTEGER(4) at (1)

result: 1 4 T F 1 0

Linux 64 bit, g95:

compilation: i = TRUE 1 Error: Can't convert LOGICAL(1) to INTEGER(8) at (1)

i = FALSE
1
Error: Can't convert LOGICAL(1) to INTEGER(8) at (1)

result: n.a.

Windows 32 bit, gfortran:

compilation: i = TRUE 1 Warning: Extension: Conversion from LOGICAL(1) to INTEGER(4) at (1)

i = FALSE
1
Warning: Extension: Conversion from LOGICAL(1) to INTEGER(4) at (1)

result: 1 4 T F 1 0

Windows 32 bit, g95:

compilation: i = TRUE 1 Error: Can't convert LOGICAL(1) to INTEGER(4) at (1)

i = FALSE
1
Error: Can't convert LOGICAL(1) to INTEGER(4) at (1)

result: n.a.

jtappin commented 13 years ago

On my 32-bit system, I can confirm that I see the same results as vmagnin. The following code shows that a gboolean is a 4-byte quantity. I would expect the mismatch to cause chaos on a big-endian processor. On a little-endian one since (I think) only the LSbit is used it shouldn't have any effect apart from possible alignment problems for subsequent pass-by-value arguments.

#include <gtk/gtk.h>
#include <stdio.h>
int main(){
  gboolean  isit;
  printf("%d\n", sizeof(gboolean));
  isit = FALSE;
  printf("%d\n", isit);
  isit = TRUE;
  printf("%d\n", isit);
}
/*
gcc gb.c `pkg-config --cflags gtk+-2.0` `pkg-config --libs gtk+-2.0` -o gb
*/

Results: 4 0 1

I'll check up on the 64-bit system tomorrow (It's at work).

jtappin commented 13 years ago

I just did an ugly brute-force test by replacing all occurrences of "logical(c_bool)" with "logical(4)" in gtk-auto-f90 and menu.f90 on my 32-bit box and rebuilding [loads of warning about possible non-C-interoperable types but it builds] and guess what -- the menu is now aligned at the top. (Obviously not a solution but it does tell us where the problem is).

jerryd commented 13 years ago

It looks to me that gboolean is basically a kind=4 integer and cbool is a kind=1 so its size in memory does not align with gboolean. In other words setting the logical value of a gboolean is not setting the upper three bytes so you get whats in there.

So try this:

logical(kind=4), parameter :: TRUE = .true. logical(kind=4), parameter :: FALSE = .false.

And see if this makes a difference.

vmagnin commented 13 years ago

../examples/menu.f90:251.22:

box = gtk_vbox_new (FALSE,0) 1 Error: Type mismatch in argument 'homogeneous' at (1); passed LOGICAL(4) to LOGICAL(1) ../examples/menu.f90:253.94:

_start (box, gtk_ui_manager_get_widget (menu_manager, "/MainMenu"//CNULL), FALS 1 Error: Type mismatch in argument 'expand' at (1); passed LOGICAL(4) to LOGICAL(1)

bonanza commented 13 years ago

I changed additionally the argument declarations in gtk-auto.f90 to logical(kind=4). Then I got warnings like: Warning: Variable 'expand' at (1) is a parameter to the BIND(C) procedure gtk_box_pack_start' but may not be C interoperable

But: I got top aligned menus with gfortran under Windows 32 bit!

jtappin commented 13 years ago

Just a quick correction. I was wrong about least significant bit, both gcc & gfortran treat any non-zero value as TRUE, so any junk in the top 3 bytes would cause an incorrect TRUE interpretation.

[I've been doing too much IDL where odd values are true and evens are false]

vmagnin commented 13 years ago

In GTK+, False and True values are defined by

define FALSE (0)

define TRUE (!FALSE)

typedef int gint;

typedef gint gboolean;

vmagnin commented 13 years ago

Following bonanza post, if I remove the definition of gboolean from cfwrapper.py, it uses the definition of gboolean as an int. So all the logical(c_bool) are replaced by integer(c_int) in gtk-auto.f90

In gtk.f90, I then use: integer(c_int), parameter :: TRUE = 1 integer(c_int), parameter :: FALSE = 0

menu.f90 then compiles and runs correctly on my 32 bits machine. The compiler prints some warnings because booleans are still declared as logical in menu.f90. In each example, logicals should be replaced by integers. It also means we should use + and * operators instead of .and. and .or.

Before commiting anything, I will try to modify and test each example and I will wait your opinions on the subject.

jtappin commented 13 years ago

I guess then the proper thing to do is to translate "gboolean" to "integer(c_int)" and to define true & false as integer(c_int), parameter :: FALSE = 0 integer(c_int), parameter :: TRUE = not(FALSE)

Using "not(FALSE)" rather than -1 on the off chance that someone somewhere is still using a 1's complement processor.

jtappin commented 13 years ago

I think the proper way to handle integers being used as logicals would be to use the IAND and IOR intrinsics (and the other bit intrinsics as needed). e.g. if (a .and. b) ..... would become if (iand(a, b) == TRUE) ......

bonanza commented 13 years ago

imho, the proposal of jtappin should be implemented.

vmagnin commented 13 years ago

I created a new branch "test" where I replaced all logical(c_bool) by integer(c_int) in the project. And I took jtappin proposal into account. I used the following definitions: integer(c_int), parameter :: FALSE = 0 integer(c_int), parameter :: TRUE = not(FALSE)

Everything seems to work, but tests.f90 gives me an error: in Fortran TRUE is -1, but in GTK it is +1 (see jtappin post 21 hours ago). Why not(FALSE) is -1 in Fortran and !FALSE is +1 in C ?
Should we write: integer(c_int), parameter :: TRUE = 1 ? But will !FALSE be 1 with every architecture ?

We could also use a GTK+ function returning a TRUE value to be sure. For example: g_hostname_is_ip_address("192.168.0.1"//CNULL)

jtappin commented 13 years ago

According to Harbison & Steele "C, A reference Manual" (1987), the ! operator is a logical negation. "The result of the ! operator is of type int; the result is 1 if the operand is zero (null in the case of pointers, 0.0 in the case of floating point values) and 0 if the operand is not zero (nonnull, not 0.0). The result is not an lvalue. The expression !(x) is identical in meaning to (x)==0."

So I was wrong in suggesting not(FALSE) as an appropriate way of setting TRUE. TRUE=1 is correct.

jerryd commented 13 years ago

yes, just set the constant TRUE = 1, I suspected gboolean was an integer. Thanks for all your efforts

jtappin commented 13 years ago

Just built & run all the examples using the "test" branch (after changing the definition of TRUE to 1) on my 32-bit Linux box using gfortran.

All build & run. menu.f90 has the correct (top) alignment. I don't see any errors introduced.

vmagnin commented 13 years ago

I just commited gtk.f90 with: integer(c_int), parameter :: TRUE = 1 Every example works fine (menu.f90 included) on my 32 bits linux machine with gfortran. Before merging devel and test branches, I will wait news about what happens now on 64 bits machines. Thanks for all your contributions, and particularly for the useful citation from "C, A reference Manual" (1987).

bonanza commented 13 years ago

On my 64 bit Linux machine all examples work fine now also.

bonanza commented 13 years ago

But another issue catched my eye: If the menu example is started from another directory, it produces an error "Gtk-CRITICAL *_: gtk_box_pack: assertion `GTK_IS_WIDGET (child)' failed". That means, it searches for menu.xml only in the current directory and not in the directory where the executable resides. May it is better to use ui = gtk_ui_manager_add_ui_from_string (menu_manager, trim(buffer)//CNULL, lentrim(buffer,8), error) where buffer is a string parameter with the xml definition: character(len=),parameter:: buffer = & ""//C_NEW_LINE//& " <menubar name=""MainMenu"">"//C_NEW_LINE//& " <menu name=""FileMenu"" action=""FileMenuAction"">"//C_NEW_LINE//& " <menuitem name=""Open"" action=""OpenAction"" />"//C_NEW_LINE//& " <menuitem name=""Save"" action=""SaveAction"" />"//C_NEW_LINE//& " <menuitem name=""Close"" action=""CloseAction"" />"//C_NEW_LINE//& " <menuitem name=""Quit"" action=""QuitAction"" />"//C_NEW_LINE//& " "//C_NEW_LINE//& " <menu name=""EditMenu"" action=""EditMenuAction"">"//C_NEW_LINE//& " <menuitem name=""Cut"" action=""CutAction""/>"//C_NEW_LINE//& " <menuitem name=""Copy"" action=""CopyAction""/>"//C_NEW_LINE//& " <menuitem name=""Paste"" action=""PasteAction""/>"//C_NEW_LINE//& " "//C_NEW_LINE//& " <menu name=""HelpMenu"" action=""HelpMenuAction"">"//C_NEW_LINE//& " <menuitem name=""Help"" action=""HelpAction""/>"//C_NEW_LINE//& " "//C_NEW_LINE//& " "//C_NEW_LINE//& "" Then the menu.xml file is no longer needed.

bonanza commented 13 years ago

Ooops, I accidently closed the issue. Sorry....

vmagnin commented 13 years ago

I included and commited your string in menu.f90 (test branch only), but I replaced len_trim(buffer, 8) by len_trim(buffer, c_size_t), because on my 32 bits machine I obtained the following error: ui = gtk_ui_manager_add_ui_from_string (menumanager, trim(buffer)//CNULL, len Error: Type mismatch in argument 'length' at (1); passed INTEGER(8) to INTEGER(4)

But g95 does not accept two arguments for len_trim(), so I finally wrote: integer(c_size_t) :: buffer_length

buffer_length = len_trim(buffer)
ui = gtk_ui_manager_add_ui_from_string (menu_manager, trim(buffer)//CNULL, buffer_length, error)
vmagnin commented 13 years ago

Hi everybody, I have just merged all the branches. So please use now the "master" branch. I deleted the "test" and "devel" branches on my machine using "git branch -d test" and "git branch -d devel", but they still appear on GitHub and I have not yet found the solution to delete them... Jerry, do you have the possibility to do it ?

vmagnin commented 13 years ago

I finally found the syntax to delete a remote branch: git push origin :devel on the Pro Git book : http://progit.org/book/ch3-5.html

There's now only one branch: master.

jerryd commented 13 years ago

On 03/17/2011 05:33 AM, vmagnin wrote:

Hi everybody, I have just merged all the branches. So please use now the "master" branch. I deleted the "test" and "devel" branches on my machine using "git branch -d test" and "git branch -d devel", but they still appear on GitHub and I have not yet found the solution to delete them... Jerry, do you have the possibility to do it ?

I will have a look.

Jerry