Silverfrost Forums

Welcome to our forums

native %pl [external]

7 Mar 2020 4:05 #25051

Does anybody have a simple example of using:

create_graphics_region@

select_graphics_object@

and then diverting the output of the native %pl[external] to the created graphics region ?

I thought this was possible from some of the earlier comments on the forum, but I cannot find a way of getting it to work.

Thanks

Ken

9 Mar 2020 8:15 #25055

Ken

Here is a sample program that uses %pl[external] but not directly in the way you want.

       integer function plot()
       INCLUDE <windows.ins>
       PARAMETER(N=10)
       REAL*8 x(N),y(N)
       COMMON x,y
       CALL winop@('%pl[external]')
       CALL winop@('%pl[margin=(60,60,60,60)]')
       CALL winop@('%pl[title=Graph]') !graph title
       CALL winop@('%pl[width=2]')     !pen width
       CALL winop@('%pl[x_array]')     !x data is provided as an array
       CALL winop@('%pl[link=curves]') !join data points with curves
       CALL winop@('%pl[symbol=9]')    !mark data points with filled rhombuses
       CALL winop@('%pl[colour=red]')  !pen colour
       CALL winop@('%pl[pen_style=2]') !2=PS_DOT
       CALL winop@('%pl[tick_len=6]')
       CALL winop@('%pl[frame,gridlines]')
       CALL winop@('%pl[y_sigfigs=2]')
       CALL winop@('%pl[y_axis=y-data@(-6,10)]')
       i=winio@('%pl',N,x,y)
       plot = 2
      end function

      integer function plot1()
       INCLUDE <windows.ins>
       PARAMETER(N=10)
       REAL*8 x(N),y(N)
       COMMON x,y
       CALL winop@('%pl[external]')
       CALL winop@('%pl[title=Graph]') !graph title
       CALL winop@('%pl[x_array]')     !x data is provided as an array
       CALL winop@('%pl[link=curves]') !join data points with curves
       CALL winop@('%pl[symbol=9]')    !mark data points with filled rhombuses
       CALL winop@('%pl[colour=red]')  !pen colour
       CALL winop@('%pl[pen_style=2]') !2=PS_DOT
       CALL winop@('%pl[frame,gridlines]')
       CALL winop@('%pl[y_sigfigs=2]')
       CALL winop@('%pl[y_axis=y-data]')
       CALL winop@('%pl[dx=0.1]')
       CALL winop@('%pl[dy=0.1]')
       i=winio@('%pl',N,x,y)
       plot1 = 2
      end function
      
      integer function print1()
      C_EXTERNAL print_graphics@ '__print_graphics' (REF):INTEGER
      integer,external::plot1
      print1 = print_graphics@(plot1)
      print1 = 2
      end function

      WINAPP
      INCLUDE <windows.ins>
      INTEGER N,i
      integer,external::plot,print1
      PARAMETER(N=10)
      REAL*8 x(N),y(N)
      COMMON x,y
      DO i=1,N
        x(i)=0.1d0*(i-1)
        y(i)=x(i)*x(i)-1.0d0 
      ENDDO
      i=winio@('%ww%ca[Quadratic]%pv&')
      i=winio@('%^gr[user_resize]&',400,250,plot)
      i=winio@('%sf%ff%nl%cn%^tt[Print]',print1)
      END
9 Mar 2020 10:03 #25060

Thanks John, I had come across that example before.

Paul, thanks for your example.

Looking through your code, the first error I see that I have been making using %pl[external] is specifying the size of the graphics region in the winio@ string, this is not required since the size of the current graphics region is already defined elsewhere. This explains why I have been getting an error about the third variable being integer and not real*8.

I will continue to experiment.

Many thanks

Ken

9 Mar 2020 2:16 #25062

Success. Here is an example for those that at curious. Note that a call to simpleplot_redraw@ does not update the %pl connected to a graphics region in memory. Hence the subroutine update called from within a main loop. With this approach, the flicker when a %pl region embedded in a window is updated with large data sets is eliminated.

winapp
module data_mod 
implicit none 
integer, parameter       :: dp = kind(1.d0)
integer, parameter       :: npts_max = 100000 
integer                  :: npts = 5000, npts_now(2) = 0 
real(kind=dp)            :: x(npts_max) = 0.d0, y(npts_max) = 0.d0
integer                  :: internal_id = 1, plot_id = 2 
end module data_mod 

module calc_mod 
use data_mod 
implicit none 
contains 
  integer function build_gui() 
  include<windows.ins> 
  integer i
    i = winio@('%mn[Exit]&','exit') 
    i = winio@('%bg[grey]&') 
    i = winio@('%3.1ob%ws%cb&','Number of points')  
    i = winio@('%il&', 0, npts_max) 
    i = winio@('%rd%cb&',npts)    
    i = winio@('%^tt[Plot]%cb&',plot) 
    i = winio@('%ff&') 
    i = winio@('%`gr[black]&',650,600,plot_id)
    i = winio@('%ff') 
    build_gui = 1 
  end function build_gui 

  integer function plot() 
  include<windows.ins> 
  integer i, counter   
    counter = 0
    x(1) = 0.d0 ; y(1) = 0.d0 
    do i = 2, npts, 1
      x(i) = x(i-1) + 0.5d0 ; y(i) = y(i-1) + 0.5d0 
      npts_now = i   
      counter = counter + 1
      if (counter .eq. 20 )then 
        call YIELD_PROGRAM_CONTROL@(Y_TEMPORARILY)
        call update
        counter = 0 
      end if
    end do 
    plot = 1 
  end function plot


  subroutine update
  include<windows.ins>
  integer ig, icopy
    ig = create_graphics_region@(internal_id,650,600)
    ig = select_graphics_object@(internal_id)
    ig = winio@('%fn[Tahoma]&')
    ig = winio@('%ts&',1.1d0)
    call winop@('%pl[native,smoothing=4,width=3,x_array,independent,N_GRAPHS=1, gridlines,y_sigfigs=2]') 
    call winop@('%pl[link=lines,colour=blue,symbol=0,pen_style=0,frame,tick_len=10,axes_pen=4]')
    call winop@('%pl[title='A straight line',x_axis='x data',y_axis='y data']') 
    ig = winio@('%`bg[white]&') 
    ig = winio@('%pl[external]',npts_now,x,y) 
    icopy = COPY_GRAPHICS_REGION@(plot_id,     0, 0, 650, 600,  &
                                  internal_id, 0, 0, 650, 600, SRCCOPY )  !13369376 
    ig = delete_graphics_region@(internal_id)
  end subroutine update

end module calc_mod 

program main 
use calc_mod 
implicit none 
integer i 
  i = build_gui() 
end program main 
11 Mar 2020 11:45 #25078

Paul, Is my statement

Note that a call to simpleplot_redraw@ does not update the %pl connected to a graphics region in memory.

correct? Or do I need to look at what I was trying to do again? Probably does not matter since I got to where I wanted to be, but if I am incorrect then there may be the opportunity to increase the execution speed. Thanks Ken

11 Mar 2020 12:11 #25079

Ken

I don't have a quick answer to your question. It would take me a while to work out how your program works and where simpleplot_redraw@ might be called. But I don't see how simpleplot_redraw@ could change the input data.

12 Mar 2020 11:13 #25084

Paul, No need to worry about it. I just thought you might come back and say it should definitely work. John, same result with PLOT_REDRAW@(). Below is the code which demonstrates that the update does not occur.

Ken

12 Mar 2020 11:20 #25085
 module data_mod 
implicit none 
integer, parameter       :: dp = kind(1.d0), npts_max = 10000 
integer                  :: npts = 2000, npts_now(2) = 0 
real(kind=dp)            :: x(npts_max) = 0.d0, y(npts_max) = 0.d0
integer, save    :: internal_id = 1, plot_id = 2 
end module data_mod 

module calc_mod 
use data_mod 
implicit none 
contains
 
  integer function build_gui() 
  include<windows.ins> 
  integer i

    ! Draw first 2 points to a pl in memory
    npts_now = 2
    x(1) = 0.d0 ; y(1) = 0.d0 ; x(2) = 1.d0 ; y(2) = 1.d0

    i = create_graphics_region@(internal_id,650,600)
    i = select_graphics_object@(internal_id)

    call winop@('%pl[native,smoothing=4,width=1,x_array,independent,N_GRAPHS=1, gridlines,y_sigfigs=2]') 
    call winop@('%pl[link=lines,colour=blue,symbol=0,pen_style=0]') 
    i = winio@('%`bg[white]&') 
    i = winio@('%pl[external]',npts_now,x,y)

!   Comment out above four lines and remove comment from line below.  This demonstrates that the COPY_GRAPHICS_REGION@ call works.

!$$$$$$     call draw_filled_rectangle@(0,0,650,600,rgb@(0,255,0)) 

    i = winio@('%mn[Exit]&','exit') 
    i = winio@('%bg[grey]&') 
    i = winio@('%3.1ob%ws%cb&','Number of points')  
    i = winio@('%il&', 0, npts_max) 
    i = winio@('%rd%cb&',npts)    
    i = winio@('%^tt[Plot]%cb&',plot) 
    i = winio@('%ff&') 
    i = winio@('%`gr[black]&',650,600,plot_id)   ! Initially black so that we can see image copied over

!   Following lines are same as %pl above (except for graphics size), to see embedded plot being updated live as calculation proceeds
!
!$$$$$$     call winop@('%pl[native,smoothing=4,width=1,x_array,independent,N_GRAPHS=1, gridlines,y_sigfigs=2]') 
!$$$$$$     call winop@('%pl[link=lines,colour=blue,symbol=0,pen_style=0]') 
!$$$$$$     i = winio@('%`bg[white]&') 
!$$$$$$     i = winio@('%ta%pl&',650,600,npts_now,x,y)

    i = winio@('%ff') 
    build_gui = 1 
  end function build_gui 

  integer function plot() 
  include<windows.ins> 
  integer i, icopy, counter 
  real(kind=dp) ang_last
  integer COPY_GRAPHICS_REGION@  
    ang_last = 0.d0 ; counter = 0 
    do i = 3, npts, 1
      x(i) = x(i-1) + 1.d0 ; y(i) = y(i-1) + 1.d0 ; npts_now = i ; counter = counter + 1
      if (counter .eq. 10 )then 
        call YIELD_PROGRAM_CONTROL@(Y_TEMPORARILY)
           
        ! Here the call to simpleplot_redraw@ does not update the image in memory ##############
        ! We can see this since the image copied back to the screen never changes.
        ! The image that is always copied back is the %pl with the first two points as defined in function build_gui()
        call simpleplot_redraw@()
      ! call PLOT_REDRAW@()     ! John's suggestion
        icopy = COPY_GRAPHICS_REGION@(plot_id,     1, 1, 650, 600, &
                                      internal_id, 1, 1, 650, 600, 13369376 )
        if (icopy .eq. 1) write(6,*) 'Success for COPY_GRAPHICS_REGION@'
        counter = 0 
      end if
    end do 
    plot = 1 
  end function plot 
end module calc_mod 

program main 
use calc_mod 
implicit none 
integer i 
  i = build_gui() 
end program main 
14 Dec 2020 12:54 #26777

This provides a little more insight to the issue with %pl[external] and SIMPLEPLOT_REDRAW@.

https://www.dropbox.com/s/29yvovq3cvxmktr/plexternal2.f95?dl=0

The main window contains a graphics region, and two buttons for callbacks.

The first button “new_data”, creates a new data set. A new internal graphics region is created, the native %pl draws to this, the internal image is copied to the main graphics region, and then the internal graphics area is deleted. This button can be selected with the correct response each time.

The second button “new_data_2” uses a different approach after creating the new data. On it’s first run a new internal graphics region is created and again the native %pl draws to this, then the image is copied across to the main %gr region. In this call back the internal graphics region is not deleted. On subsequent calls SIMPLEPLOT_REDRAW@ is used to update the internal %pl. This does not appear to operate on the second or subsequent consecutive clicks on “new_data_2”. So SIMPLEPLOT_REDRAW@ does not work in this context. This is the behaviour reported previously in March 2020.

However after selecting button “new_data_2” a few times, then selecting “new_data” and immediately afterwards selecting “new_data_2” the plot is correctly updated – even although this is not its first call. In this case it behaves as expected, however a subsequent click on “new_data_2” then fails.

So using a call to SIMPLEPLOT_REDRAW@ to update a %pl[external] region does work correctly on some occasions.

Ken

Please login to reply.