Silverfrost Forums

Welcome to our forums

64 bit ClearWin+

25 Jun 2013 10:17 #12483

We observed an inconsistency when using files$ from ClearWin64+. Parameter 2 of call files$ should return the number of files specified via pattern (parameter 1). However, parameter 2 seems to return a number which is 1 less than we expect. We temporarily modified file clrwin.f95 and changed subroutine files$ as appropriate. This made files$ return the value we expected.

25 Jun 2013 2:03 #12486

I have logged these issues for investigation.

26 Jun 2013 10:50 #12497

I have fixed these two bugs for the next beta release of 64 bit ClearWin.

12 Jul 2013 7:51 #12594

I am working with DietmarSiepmann on the same project together. A big part of our main gui application is ported. Now I have discovered another problem using the format code %mn %dl and %lw. The problem occurs with the Intel Fortran (64bit) Compiler and the ClearWin64 dll only. With Salford FTN95 (32bit) and gFortran (64bit) there is no problem and the test program works fine. Maybe there is a bug? But on which side?

The following source code demonstrates the problem:

      program test
      
      use mswin$
      
      integer*4 i, j,control,F_TIM1
      REAL*8 R8
      external F_TIM1

      i=winio$('%ww[no_border]&')
      i=winio$('%mn[open]&',F_TIM1)
      R8=3.0
!      i=WINIO$('%dl&',R8,F_TIM1)
      i=winio$('%pv%fr&',400_4,300_4)
      i=winio$('%lw',control)   
      
      do j=1,10
       i=F_TIM1()
      enddo

      end

      FUNCTION F_TIM1()
      INTEGER*4 F_TIM1,I4
      LOGICAL*4 LOGIC
      I4=70
      WRITE(*,*)' F_TIM1'      
      INQUIRE(UNIT=I4, OPENED=LOGIC) !+ INQIURE closes the program used with %lw %dl or/and %mn
      IF(LOGIC) THEN
       WRITE(*,*)' LOGIC TRUE'      
      ELSE
       WRITE(*,*)' LOGIC FALSE'      
      ENDIF
      F_TIM1=1
      END

The function F_TIM1 works for itself fine. The program will be closed automatically only when I’m using the format code %lw in combination of %dl and %mn (clicking on the menu ,,open'). I need the ,,inquire” statement in this function and exactly this call provides the problem in combination of %lw %dl and %mn.

If I dont use the formate code %lw and use %mn and %dl only then the application works fine with all compilers (32bit and 64 bit). But I need the format code %lw in the application too.

12 Jul 2013 3:56 #12600

The instructions advise calling stop_when_windows_close$() after using %lw.

12 Jul 2013 11:57 #12602

Never heard about stop_when_windows_close$() How it works?

13 Jul 2013 4:15 #12603

This subroutine is only needed for some 64 bit programs. It is effectively the same as yeild_program_control$(y_permanently).

15 Jul 2013 7:37 #12611

I have not heard about it. I have added this call into the program and everything works fine now. Many thanks for the advice.

23 Jul 2013 3:23 #12684

We have a Salford application which creates a window using the format code '%gr'. In the callback corresponding to '%gr' we retrieve and print out the mouse position as soon as the mouse pointer is moved (making use of function get_mouse_info@ (32 bit) or get_mouse_info$ (64 bit)).

This works properly for Salford 32 bit compile environment and for the 64 bit compile environments gFortran and ifort (64 bit).

We have a modification of that scenario: we implemented one more function, say F_TIM, which will be executed, if the user hits a push button (format code '%bt'). F_TIM contains a while loop which retrieves and prints out the mouse position. The while loop may be left by depressing the right button of the mouse.

This works fine for the Salford 32 bit compile environment. The mouse position is printed out correctly in function F_TIM and left correctly.

For 64 bit compile environments gFortran and ifort (64 bit) function F_TIM is entered correctly if the corresponding push button is hit. However, as soon as the loop is entered, the first mouse position is correct, but the mouse positions following do not change even if the mouse is moved. The loop cannot be left by depressing the right button of the mouse and hence we run into an endless loop.

This is a difference to the behaviour on 32 bit.

Here is our code for Salford 32 bit:

program test
!      USE MSWIN$
      INCLUDE <WINDOWS.INS>  
      
      integer*4 i,IGR,control,F_TIM1,w,h,F_GR,hwnd
      
      external F_TIM1,F_GR
      

      i=winio@('%ww[no_border,independent]&')
      i=winio@('%hw&',hwnd)
      i=winio@('%mn[open]&',F_TIM1)
      w=300
      h=300
      i=winio@('%`^gr[rgb_colours,black,full_mouse_input]&',
     * w,h,IGR,F_GR)
      i=winio@('%pv%fr%ff&',400,300)
      i=winio@('%^bt[Test]&',F_TIM1)
      
      i=winio@('%lw',control)   
      
!      call stop_when_windows_close@()
      
      end
      
            
      FUNCTION F_GR()
      INTEGER*4 F_GR
      F_GR=4
      RETURN
      END
      
      FUNCTION F_TIM1()
!      USE MSWIN$
      INCLUDE <WINDOWS.INS>       
      integer*4 F_TIM1,PAR1,PAR2,PAR3,I
      LOGICAL*4 LOGIC      
      F_TIM1=2
      LOGIC=.TRUE.
      I=0
      DO WHILE (LOGIC)
       I=I+1
       call get_mouse_info@(PAR1,PAR2,PAR3)
       WRITE(*,*)'get_mouse_info (loop 1): ',PAR1,PAR2,PAR3 ,I   
       IF(PAR3.eq.2) LOGIC=.FALSE.
      ENDDO
      END

We created the corresponding exe file for Salford 32 bit compile environment by means of command

          ftn95 test.for /link /windows

If we do not use the /windows option for the Salford 32 bit compile, the behaviour for all the compiler platforms mentioned are the same (and do not produce the correct mouse pointer coordinates).

For gFrotran we also tried compiling with option -mwindows , but this did not work, as well.

23 Jul 2013 4:56 #12685

You should be able to see the source code for get_mouse_info$ in clrwin.f95 (this is from memory, I don't have the files to hand).

I will take a look when I can.

23 Jul 2013 6:13 #12686

Quoted from DietmarSiepmann

We have a modification of that scenario: we implemented one more function, say F_TIM, which will be executed, if the user hits a push button (format code '%bt'). F_TIM contains a while loop which retrieves and prints out the mouse position. The while loop may be left by depressing the right button of the mouse.

Why use while loop for getting the mouse info? It will effectively block the rest of the program as the loop runs.

You could process the mouse input directly in the %gr callback:

module data
  implicit none
  include <WINDOWS.INS>

  logical :: button_state = .FALSE.


  contains
    function F_GR()
      integer :: F_GR
      integer :: mx, my
      character (len=20) :: reason


      mx = clearwin_info@('graphics_mouse_x')
      my = clearwin_info@('graphics_mouse_y')
      
      if (button_state) write(*,*) 'mouse x:', mx, ' mouse y:', my

      reason = CLEARWIN_STRING@('CALLBACK_REASON')

      if (reason == 'MOUSE_LEFT_CLICK') then
        button_state = .TRUE.
      else if (reason == 'MOUSE_RIGHT_CLICK') then
        button_state = .FALSE.
      end if
      
      F_GR = 1

    end function F_GR


    function F_BT()
      integer :: F_BT

      if (button_state) then
        button_state = .FALSE.
      else 
        button_state = .TRUE.
      end if

      F_BT = 2
      
    end function F_BT


end module data


program test
  use data
  implicit none 

  integer*4 i,control,hwnd 
 
  i=winio@('%ww[no_border,independent]&') 
  i=winio@('%hw&',hwnd) 
  i=winio@('%^gr[rgb_colours,black,full_mouse_input]&', 300,300,F_GR) 
  i=winio@('%ff%^bt[Test]&',F_BT) 
  i=winio@('%lw',control)           
  !call stop_when_windows_close@()       
end
24 Jul 2013 7:37 #12687

We are aware of being able to process mouse button events in %gr callback and we have tried to state that this works (for 32 bit and 64 bit) in our previous post.

However, we try to port a big existing application from 32 bit to 64 bit. This application has been designed using the scenario with function F_TIM described in the previous post and which does not behave in the same way for 64 bit as under 32 bit. We would try to change as less as possible in the port and that's why we tried to use the F_TIM scenario which works under Salford (32 bit) to our satisfaction.

24 Jul 2013 10:45 #12688

I'm astonished that the function works anywhere outside of a %gr or %dw area, because when I read FTN95.CHM it clearly states 'To obtain the position of the mouse, the mouse buttons, and the keyboard shift keys [u:8b779a77f1]at the time when the last owner-draw (%^dw) or graphics region (%^gr) call-back function was called[/u:8b779a77f1].' and 'This routine should be called immediately on entry to the call-back function. It does not make sense to call this function in other contexts. '

There is a certain obviousness that the function is tied to a %gr or %dw by the origin of coordinates, and any %bt is certainly external to a graphics area.

Hence Jalih's suggestion relates to the way that Clearwin+ seems to be intended to work.

No doubt the button could be triggered by a key press while the mouse pointer remains in the %gr area, but whether triggered by a key press or a mouse click, the %gr has lost the focus. While you are in the callback for the button, the %gr region cannot reclaim the focus. As a result, I repeat that I am surprised that your approach works in 32 bit FTN95 mode

If I was programming your application, I might put a popup menu in the %gr region with options for 'start mouse tracking' and 'stop mouse tracking', and keep GET_MOUSE_INFO@ entirely within the graphics callback.

Eddie

24 Jul 2013 12:56 #12689

Quoted from DietmarSiepmann

However, we try to port a big existing application from 32 bit to 64 bit. This application has been designed using the scenario with function F_TIM described in the previous post and which does not behave in the same way for 64 bit as under 32 bit. We would try to change as less as possible in the port and that's why we tried to use the F_TIM scenario which works under Salford (32 bit) to our satisfaction.

I previously mentioned, that your do while loop is taking up the cpu and blocking the handling of window messages in the application.

Add a call to TEMPORARY_YIELD@() function at the bottom of the do while loop and it should probably work.

24 Jul 2013 2:59 #12690

Thanks to all who helped in this topic, especially to Jalih. Jalih's information to call TEMPORARY_YIELD@() function at the end of the while loop was right and made our test application also work for 64 bit as we expected (and this for ifort and gFortran).

Although our proceeding might not be the correct one, we would use it since it seems to work and thus we do not have to do so many code changes.

Dietmar

25 Jul 2013 9:53 #12691

Also besides call temporary_yield@ look at simultaneous use of PERMIT_ANOTHER_callback, might be very helpful for complex GUI. You can call it many times, i do not know the limit, never had any problems with that

27 Jul 2013 6:47 #12694

I have have now looked at this issue and the correspondence above has correctly resolved the problem.

29 Jul 2013 1:47 #12701

One of our SALDORD applications to be ported from 32 to 64 bit makes use of call 'GET_WKEY1@'. I could not find GET_WKEY1 in clearwin64.dll/clearwin64.a . Is it planned to add it to the dll?

29 Jul 2013 2:01 #12702

I can add this and any similar routines on request. There are a few routines like this that will work but I have assumed that they are redundant.

29 Jul 2013 2:26 #12705

I have now added this function to the beta download (ClearWin64.exe).

Please login to reply.