Silverfrost Forums

Welcome to our forums

Native %pl

28 Oct 2017 11:13 (Edited: 28 Oct 2017 8:40) #20582

Paul,

My answer could be surprising and i hope you will like it: with LOG scale you do not have to worry about limits or try to implement them. Just use for the LOG plots limits usual natural limits the plotting data has. Everyone doing exactly that as a #1 option and generally it looks very good with LOG plots.

The 'exact decade limits' i posted two posts back here (or the ones posted by Ken earlier) is another options for LOG scale plotting but we used it as a hack only because currently LOG scale plotting has a bug and it can not use existing plotting data min and max as its limits. Or, saying more precise, it can use but has bugs there, so the tic marks all are wrong and plot itself often goes out of frame. Older Simpleplot %pl works fine here, see the source code and the picture i posted also here week or two back on page 9. Just implementing the same will solve most of our LOG plotting problems. https://s25.postimg.org/4w58sezdb/Simpleplot.jpg

The 'exact decade limits' can be done only temporally or as a second option. If you will do that like i or Ken posted then you have to take in mind that in my case i used restriction 1e-30 which is used only because %pl does not accept double precision numbers for the limits like 1d-50 or 1d150 (unless i am mistaken, and this was already fixed, i did not check this lately)

28 Oct 2017 1:01 #20583

Silicondale

Item (2) has already been added for the next release.

28 Oct 2017 3:16 #20584

Paul - many thanks. I thought I had seen that.

Still the problem remains that if you have 10 or more separate sets of data to plot, the winio@('%pl',...) argument list quickly becomes very long and unwieldy. If using a colour-ramp as in my example a few posts back (Oct 16, 2017 12:36 pm), it would be impossible to use anything like the full set of colours available (maybe 255 or more).

Also you need to know beforehand exactly how many sets of data you want to plot - though of course you can define a maximum number and some of the x,y arrays can be zero-length.

These problems would both be avoided if each x,y point could carry its own attributes - symbol, size, colour, and type of link from the previous point - in separate arrays. If you could implement this, then the need for multiple arrays and use of N_GRAPHS and long argument lists can possibly be avoided altogether.

Having said all this - it's just suggestions for improvement. I think the native %pl is an excellent set of tools! It takes a lot of the pain out of plotting.

28 Oct 2017 7:06 (Edited: 28 Oct 2017 7:23) #20585

Paul, I not sure that you get a consensus on what are 'nice' limits with users coming from very different subject areas. The overall objective, which I think we could all agree on is to get acceptable limits for xmin and xmax, a reasonable dx value, and minimise the wasted space on the axis.

Here's my initial thoughts below on how this might be done for linear scales - see subroutine select_scale. This is based on the routine I mentioned previously (page 1), with the slight variation that the routine is called a number of times with different numbers of intervals to find a combination that limits wasted space.

For the log scales 'exact decade limits' whilst not essential in general, would netherthelss be a valuable 'option' for those of us working in the electrical power world.

Ken

28 Oct 2017 7:08 #20586
      winapp
      program main
      implicit none
      real(kind=2) xmin, xmax, xminp, xmaxp, dist
      integer i
      real(kind=2) genran ; external genran
      write(6,'(7(A20,2X))') 'Xmin','Xmax','Xminp','Xmaxp','Dist', 'Divisions','Fill %'
      do i = 1, 1000, 1
        xmin = genran()
        xmax = genran()
        if (xmin .gt. xmax) call swap(xmin,xmax)
        call select_scale( xmin, xmax, xminp, xmaxp, dist)
        write(6,'(E20.4,2X,E20.4,2X,E20.4,2X,E20.4,2X,E20.4,2X,F20.4,2X,F20.4)') &
                  xmin, xmax, xminp, xmaxp, dist, (xmaxp-xminp)/dist, (xmax-xmin)/(xmaxp-xminp)*100.d0
      end do
      end program main

      subroutine swap(a,b)
      real(kind=2), intent(inout) :: a, b
      real(kind=2) d
        d = a ; a = b ; b = d
      end subroutine swap
      
      real(kind=2) function genran()
      real(kind=2) ran
        genran = 5000.d0*random()  ; ran = random()
        if (ran .gt. 0.5d0) genran = - genran
      end function genran
      
      subroutine select_scale( xmin, xmax, xminp, xmaxp, dist)
      implicit none
      real(kind=2), intent(in) :: xmin, xmax
      real(kind=2), intent(out) :: xminp, xmaxp, dist
      integer, parameter :: ntests = 6
      integer, dimension(1:ntests) :: n_l = (/ 3, 4, 5, 6, 8, 10 /)
      real(kind=2),dimension(1:ntests) :: xminp_r, xmaxp_r, dist_r, range_r
      integer i, minrange(1)
      do i = 1, ntests
        call scale1 (xmin, xmax, n_l(i), xminp_r(i), xmaxp_r(i), dist_r(i))
        range_r(i) = xmaxp_r(i) - xminp_r(i)
      end do
      minrange = minloc(range_r)
      xminp = xminp_r(minrange(1))
      xmaxp = xmaxp_r(minrange(1))
      dist  = dist_r(minrange(1))
      contains
      subroutine scale1 ( xmin, xmax, n, xminp, xmaxp, dist )
      implicit none
      real(kind=2), intent(in) :: xmin, xmax
      integer, intent(in) :: n
      real(kind=2), intent(out) :: xminp, xmaxp, dist
      integer i, m1, m2, nal
      real(kind=2) a, al, b, del, fn, fm1, fm2
      real(kind=2), dimension(1:3) :: vint(4) = (/ 1.d0, 2.d0, 5.d0, 10.d0 /)
      real(kind=2), dimension(1:3) :: sqr(3) = (/ 1.414214d0, 3.162278d0, 7.071068d0/)
      del = .00002d0
      fn = n
      a = ( xmax - xmin ) / fn
      al = log10 ( a )
      nal = al
      if ( a .lt. 1.d0 ) nal = nal - 1
      b = a / 10.d0**nal
      do i = 1, 3
        if ( b .lt. sqr ( i ) ) goto 30
      end do
      i = 4
30    dist = vint(i) * 10.d0**nal
      fm1 = xmin / dist
      m1 = fm1
      if ( fm1 .lt. 0.d0 ) m1 = m1 - 1
      if ( abs ( float ( m1 ) + 1.d0 - fm1 ) .lt. del ) m1 = m1 + 1
      xminp = dist * float ( m1 )
      fm2 = xmax / dist
      m2 = fm2 + 1.d0
      if ( fm2 .lt. ( -1. ) ) m2 = m2 - 1
      if ( abs ( fm2 + 1. - float ( m2 ) ) .lt. del ) m2 = m2 - 1
      xmaxp = dist * float ( m2 )
      if ( xminp .gt. xmin ) xminp = xmin
      if ( xmaxp .lt. xmax ) xmaxp = xmax
      return
      end subroutine scale1
      end subroutine select_scale
28 Oct 2017 10:47 #20587

Couple minor comments about LOG plotting (in the post above i was talking only about LOG plotting. Here I also do not touch linear plotting)

I use both exact decade limits in LOG plotting (i.e. rounding actual data limits to exact decade, for those who did not follow discussion above, or using 1 and 1000 limits if actual plotting data minimum and maximum are at, say, 3 and 500) and actual data limits (where limits are just data limits, or 3 and 500) in my own plotting for decades. There exist one negative property of exact decade plotting when displaying changing data in realtime. Imaging you drive the car and measure its speed: the plot permanently jumps when the data minimum or maximum switch to the next decade making you crazy. In my extreme electrical power world the operator will think that this was North Korean nuc attack on the power grid.:) With the actual data limits the LOG plot or the numbering move smoothly.

But there also exist one positive property of exact decade limits in LOG plotting and it is specific only to %pl: it is needed to prevent new %pl from switching to linear plotting if numbers get to zero or negative or crash. Same can be done though by additional call to winop@('%pl[y_min=some_min_value]').

There actually is nothing to debate or get a consensus in LOG plotting. The LOG plot numbering is MUCH simpler then LINEAR:

  1. Ideally to get both options for LOG plotting: the actual data limits like in linear and log plotting in older Simpleplot and the exact decades limits. Do not see here any problems with the consensus among the users. May be just which option to make as a default. 😃.

  2. With just one option in %pl the user still can make exact decade limit plots from actual data limit plots as it was shown above, but one can not do the opposite due to bugs. The only what needed is to fix the scale, tics and numbering bugs in LOG native %pl and then reproduce one line code with LOG_LOG made in older Simpleplot %pl on page 9. This why wrote above that nothing new to do was needed given the fact how difficult the native %pl moving forward.

30 Oct 2017 2:34 #20588

This is surfplot program demo made with native %pl done in 20-30 minutes. https://s25.postimg.org/eew57eozz/Surfplot.png

It can display all 24bit gamma of colors and need less then 10 lines of code done in the function cb_Surfplot_plotting, the rest is just definition of function and usual GUI and XY plotting code. This is how simple to implement 2D graphics.

Few problems currently:

  • Why it does not work with smaller resolution then 800x600 (try to resize it with mouse)?
  • Why it does not like INCLUDE <clearwin.ins> and needs USE clrwin ?
  • Why RGB colors inverted BGR?

Was stopped on these problems for 10x more time then these 20-30 minutes

module modSurfplotDemo
!INCLUDE <clearwin.ins>  ! does NOT work
USE clrwin
real*8 x(2),y(2), xx, yy, xx0, yy0, xx1, yy1

CONTAINS 

integer function cb_Surfplot_plotting() 

  call get_graphical_resolution@(ix_Window, iy_Window)
  ixCenter = ix_Window/2
  iyCenter = iy_Window/2

  xx =0;yy=0
  call get_plot_point@(xx, yy, xx0, yy0) 
  xx =1;yy=1
  call get_plot_point@(xx, yy, xx1, yy1) 

  Do ix = int(xx0+1), int(xx1-1) ! ix_Window
    do iy = int(yy1+1), int(yy0-1) ! iy_Window    

    xs = (ix-ixCenter)/(ixCenter+1.)
    ys = (iy-iyCenter)/(iyCenter+1.)
    radius = sqrt( xs**2 + ys**2)
    z = 0.5 * (1 + cos(33.*radius)) * exp(-2.*radius**2) 
    ir=int(z*255)
    iCol = rgb@(0,0,ir)  
     call set_pixel@(ix,iy,iCol)
    enddo  
  endDo  

  print*,'done xx0, yy0, xx1,yy1 ', xx0, yy0, xx1, yy1
  cb_Surfplot_plotting = 2 
  end function
end module modSurfplotDemo

!.....................................................
program SurfplotGUI
use modSurfplotDemo

x(1)=0;x(2)=1
y(1)=0;y(2)=1

  i = winio@('%ww&') 
  call winop@('%pl[native,x_array,N_GRAPHS=1]') 
  call winop@('%pl[scale=linear]') 
  call winop@('%pl[x_min=0.,x_max=1.,y_min=0.,y_max=1.]') 
  i = winio@('%`bg[white]&') 

  i=winio@('%sf%ts%bf%es&', 2d0)
  call winop@('%pl[framed,axes_pen=3,width=3,x_axis='Length (um)',y_axis='Width (um)']')

  i = winio@('%pv%pl%ff&',900,600,2,x,y)! ,cb_Surfplot_plotting ) 

  i=winio@('%sf%ts&', 1d0)
  i = winio@('%cn%^bt[Surfplot]%ff',   cb_Surfplot_plotting)


end Program SurfplotGUI
30 Oct 2017 5:22 #20589

Dan,

Thanks very much for the example. I have tried to learn from what you have presented and generated the following expanded version module modSurfplotDemo !INCLUDE <clearwin.ins> ! does NOT work USE clrwin integer4 i real8 x(2),y(2), xx, yy, xx0, yy0, xx1, yy1 integer(7) handle

 CONTAINS 

 integer function cb_Surfplot_plotting() 

   integer*4 ix_Window, iy_Window, ixCenter, iyCenter, ix,iy,ir, icol
   real*4    xs,ys, radius, z
!
   call get_graphical_resolution@(ix_Window, iy_Window) 
   ixCenter = ix_Window/2 
   iyCenter = iy_Window/2 

   xx =0;yy=0 
   call get_plot_point@(xx, yy, xx0, yy0) 
   xx =1;yy=1 
   call get_plot_point@(xx, yy, xx1, yy1) 

   Do ix = int(xx0+1), int(xx1-1) ! ix_Window 
     do iy = int(yy1+1), int(yy0-1) ! iy_Window    

       xs   = (ix-ixCenter)/(ixCenter+1.) 
       ys   = (iy-iyCenter)/(iyCenter+1.) 
       radius = sqrt( xs**2 + ys**2) 
       z    = 0.5 * (1 + cos(33.*radius)) * exp(-2.*radius**2) 
       ir   = int(z*255) 
       iCol = rgb@(0,0,ir)  
       call DRAW_LINE_between@(ix,iy,ix,iy,iCol) !  draw_point@ (ix,iy,iCol)
     end do  
   end Do  
   call UPDATE_WINDOW@(handle)

   print*,'done xx0, yy0, xx1,yy1 ', xx0, yy0, xx1, yy1 
   cb_Surfplot_plotting = 2 
   end function 
 end module modSurfplotDemo 

 !..................................................... 
 program SurfplotGUI 
 use modSurfplotDemo 

   x(1)=0;x(2)=1 
   y(1)=0;y(2)=1 

   i = winio@  ('%ww&')                                            ! change the style of a window
   call winop@ ('%pl[native,x_array,N_GRAPHS=1]') 
   call winop@ ('%pl[scale=linear]') 
   call winop@ ('%pl[x_min=0.,x_max=1.,y_min=0.,y_max=1.]') 
   
   i = winio@  ('%`bg[white]&')                                    ! Background colour format
   i = winio@  ('%sf&')                                            ! return to the standard font
   i = winio@  ('%ts&', 2d0)                                       ! set the text size
   i = winio@  ('%bf&')                                            ! switch to bold font
   i = winio@  ('%es&')                                            ! cause the window to close when the Escape key is pressed

   call winop@ ('%pl[framed,axes_pen=3,width=3,x_axis='Length (um)',y_axis='Width (um)']') 

   i = winio@  ('%pv&')                                            ! allow certain controls to be re-sized under user control
   i = winio@  ('%pl&',900,600,2,x,y)! ,cb_Surfplot_plotting )     ! ???  ftn95 /64 /check has problem with 7th argument ??
!
   i = winio@  ('%ff&')                                            ! Form feed. To move down to below any existing controls
   i = winio@  ('%sf&')                                            ! return to the standard font
   i = winio@  ('%ts&', 1d0)                                       ! set the text size
   i = winio@  ('%cn&')                                            ! centre text and controls in the window
   i = winio@  ('%^bt[Surfplot]&',  cb_Surfplot_plotting)          
   i = winio@  ('%ff&')                                            ! Form feed. To move down to below any existing controls
   i = winio@  ('%hw', handle)                                     ! return the handle of the current window

 end Program SurfplotGUI 

Questions:

  1. compiling with /64 /check reports error with argument 7 (??) on: i = winio@ ('%pl&',900,600,2,x,y) (I could not find the documentation of %pl for this call, which I expect is due to the recent changes.
  2. could you use draw_point@, rather than DRAW_LINE_between@ ?
  3. I found I needed update_window@, so used %hw. It appeared to work for my configuration, running in PLATO.

Thanks again for the example.

30 Oct 2017 6:34 (Edited: 30 Oct 2017 7:12) #20590

../ctd Questions:

  1. compiling with /64 /check reports error with argument 7 (??) on: i = winio@ ('%pl&',900,600,2,x,y) I could not find the documentation of %pl for this call, which I expect is contained in this very long post. Is there a 7th argument ?
  2. I needed to add integer(7) handle i = winio@ ('%hw', handle) ! return the handle of the current window and call UPDATE_WINDOW@(handle) for my environment, so that the screen updated (when running in PLATO). Is this not a requirement for your test ?
  3. Instead of using call DRAW_LINE_between@(ix,iy,ix,iy,iCol), would draw_point@ (ix,iy,iCol) work as well ?
  4. with 'iCol = rgb@(0,0,ir)', why is the display red ? I checked z is in the range [0:1]

Again, thanks Dan for the example, as it does help to understand some of the devilry that you use.

John

30 Oct 2017 7:00 #20591

John, Have fun with that, glad you are joining growing crowd of living debuggers polishing new %pl, hopefully things will go faster.

By the way compiling with /64 /check gives me no errors and screen updates by itself if screen size is larger then 800 x 600. Thanks for the hint with window update, that solves the problem for smaller size screens

draw_point@ (ix,iy,iCol) is Ok. Also set_pixel@(ix,iy,iCol) works too but only in 32 bits

BGR colors order clearly is a bug. Also both X and Y axis have range 0 - 1 but numbering mechanism by some reason made hell amount of numbers on Y axis

30 Oct 2017 7:51 #20593

Silicondale

An option [stacked] has already been added. This avoids the problem of multiple arguments by allowing you to stack the y-values etc. for the various graphs into one array.

I guess that, for refined data (allowing each point to have its own symbol etc.) we could use an array of 'user-defined' TYPE to provide the (x,y), symbol, etc. for each point in turn. If this suits your purpose then I will add it to the wish list.

30 Oct 2017 7:58 #20594

Dan,

My '7th argument' error could relate to the .dll version I am using. draw_point@ is no different to DRAW_LINE_between@

I looked at the problems of

  1. colour for rgb@
  2. speed of plotting ( which looks slow) by defining a %gr region. With %gr region, colour is fixed and also speed is much faster ( x20 faster ) I suspect these problems relate to using DRAW_LINE_between@ (ix,iy,ix,iy,iCol) in a %pl region, which may be reasonable ?

this is my %gr patched test (hope it posts - nope)

module modSurfplotDemo 
 !INCLUDE <clearwin.ins>  ! does NOT work 
 USE clrwin
 integer*4 sx, sy, w_handle
 integer*4 i 
 real*8    x(2),y(2), xx, yy, xx0, yy0, xx1, yy1 
 integer(7) handle
 logical :: test_id = .true.

 CONTAINS 

 integer function cb_Surfplot_plotting() 

   integer*4 ix_Window, iy_Window, ixCenter, iyCenter, ix,iy,ir, icol, nc, ib
   real*4    xs,ys, rad, z, dt, r2, sz, z_up, z_do, rm
!
   test_id = .not. test_id

   call get_graphical_resolution@ (ix_Window, iy_Window) 
   ixCenter = ix_Window/2 
   iyCenter = iy_Window/2 
!   xx =0; yy=1 
!   call get_plot_point@ (xx, yy, xx0, yy0) 
!   xx =1; yy=0
!   call get_plot_point@ (xx, yy, xx1, yy1)
   ib = 15 
   xx0 = ib ; xx1 = ix_Window-ib
   yy0 = ib ; yy1 = iy_Window-ib
   write (*,fmt='(/'===='/a,4(1x,f0.1))') 'start xx0, yy0, xx1,yy1 ', xx0, yy0, xx1, yy1 

   dt = elapse_sec ()

   nc = 0; sz = 0;  z_do=99999; z_up = -z_do; rm = 0
   Do ix = int(xx0+1), int(xx1-1) ! ix_Window 
     do iy = int(yy0+1), int(yy1-1) ! iy_Window    

       xs   = (ix-ixCenter)/(ixCenter+1.) 
       ys   = (iy-iyCenter)/(iyCenter+1.)
       r2   = xs**2 + ys**2
       rad  = sqrt( r2 ) 
!       z    = 0.5 * (1 + cos(33.*rad)) * exp(-2.*radius**2) 
!       z    = 0.5 * (1 + cos(33.*rad)) * exp(-2.*r2) 
       z = 0.7*rad
       ir   = int(z*255) 
!z       iCol = rgb@(ir,0,255-ir)
       iCol = rgb@(0,0,ir)
       if ( test_id) then  
         call DRAW_LINE_between@ (ix,iy,ix,iy,iCol)
       else
         call draw_point@ (ix,iy,iCol)
       end if
       nc = nc+1
       sz = sz + abs(z)
       if ( z < z_do ) z_do = z
       if ( z > z_up ) z_up = z
       if ( rad > rm ) rm = rad
     end do  
   end Do  
   call UPDATE_WINDOW@(handle)
   dt = elapse_sec () - dt

   write (*,fmt='(a,f0.3,1x,i0,1x,f0.3,a)')       'seconds = ',dt, nc, 1.e6*dt/nc,' msec/call'
   if ( test_id) then  
     write (*,*) 'call DRAW_LINE_between@ (ix,iy,ix,iy,iCol)'
   else
     write (*,*) 'call draw_point@ (ix,iy,iCol)'
   end if
   write (*,*) 'z range =', z_do, sz/real(nc), z_up
   write (*,*) 'max radius =', rm
   
   cb_Surfplot_plotting = 2 
  end function 

  real*4 function elapse_sec ()
   integer*4 tick, rate
   call system_clock ( tick, rate )
   elapse_sec = real(tick) / real(rate)
  end function elapse_sec
  
 end module modSurfplotDemo 
30 Oct 2017 8:00 #20595
!..................................................... 
 program SurfplotGUI 
 use modSurfplotDemo 
   sx = 900
   sy = 600
   w_handle = 1
   x(1)=0;x(2)=1 
   y(1)=0;y(2)=1 

   i = winio@  ('%ww&')                                            ! change the style of a window
!   call winop@ ('%pl[native,x_array,N_GRAPHS=1]') 
!   call winop@ ('%pl[scale=linear]') 
!   call winop@ ('%pl[x_min=0.,x_max=1.,y_min=0.,y_max=1.]') 
   
   i = winio@  ('%`bg[white]&')                                    ! Background colour format
   i = winio@  ('%sf&')                                            ! return to the standard font
   i = winio@  ('%ts&', 2d0)                                       ! set the text size
   i = winio@  ('%bf&')                                            ! switch to bold font
   i = winio@  ('%es&')                                            ! cause the window to close when the Escape key is pressed

!   call winop@ ('%pl[framed,axes_pen=3,width=3,x_axis='Length (um)',y_axis='Width (um)']') 

   i = winio@  ('%pv&')                                            ! allow certain controls to be re-sized under user control
!z   i = winio@  ('%pl&',900,600,2,x,y)! ,cb_Surfplot_plotting )     ! ???  ftn95 /64 /check has problem with 7th argument ??
   i = winio@  ('%`^gr[grey, user_resize, rgb_colours]&',  &
                    sx, sy,             &   ! screen dimension when not maximised
                    w_handle,           &   ! ` window handle defined in crtstart
                    cb_Surfplot_plotting)   ! ^ call back function for mouse and resize
!
   i = winio@  ('%ff&')                                            ! Form feed. To move down to below any existing controls
   i = winio@  ('%sf&')                                            ! return to the standard font
   i = winio@  ('%ts&', 1d0)                                       ! set the text size
   i = winio@  ('%cn&')                                            ! centre text and controls in the window
   i = winio@  ('%^bt[Surfplot]&',  cb_Surfplot_plotting)          
   i = winio@  ('%ff&')                                            ! Form feed. To move down to below any existing controls
   i = winio@  ('%hw', handle)                                     ! return the handle of the current window

 end Program SurfplotGUI 
30 Oct 2017 9:30 (Edited: 30 Oct 2017 9:53) #20596

John, Yes, i also noticed %gr is much faster. Why? This question is to Paul. And the %gr version does not distort RGB. Here is the same code of your simpler edition where i made just two lines change and it turns to %gr surfplot. These two places are marked with exclamation sign

module modSurfplotDemo 
 !INCLUDE <clearwin.ins>  ! does NOT work 
 USE clrwin 
 integer*4 i 
 real*8    x(2),y(2), xx, yy, xx0, yy0, xx1, yy1 
 integer(7) handle 

 CONTAINS 

 integer function cb_Surfplot_plotting() 

   integer*4 ix_Window, iy_Window, ixCenter, iyCenter, ix,iy,ir, icol 
   real*4    xs,ys, radius, z 
 
   call get_graphical_resolution@(ix_Window, iy_Window) 
   ixCenter = ix_Window/2 
   iyCenter = iy_Window/2 

   xx =0;yy=0 
   call get_plot_point@(xx, yy, xx0, yy0) 
   xx =1;yy=1 
   call get_plot_point@(xx, yy, xx1, yy1) 

  xx0=1; yy0=iy_Window; xx1=ix_Window; yy1=1  !--ADDED

   Do ix = int(xx0+1), int(xx1-1) 
     do iy = int(yy1+1), int(yy0-1) 

       xs   = (ix-ixCenter)/(ixCenter+1.) 
       ys   = (iy-iyCenter)/(iyCenter+1.) 
       radius = sqrt( xs**2 + ys**2) 
       z    = 0.5 * (1 + cos(33.*radius)) * exp(-2.*radius**2) 
       ir   = int(z*255) 
       iCol = rgb@(0,0,ir)  
       call DRAW_LINE_between@(ix,iy,ix,iy,iCol) !  draw_point@ (ix,iy,iCol) 
     end do  
   end Do  
   call UPDATE_WINDOW@(handle) 

   print*,'done xx0, yy0, xx1,yy1 ', xx0, yy0, xx1, yy1 
   cb_Surfplot_plotting = 2 
   end function 
 end module modSurfplotDemo 
!..............................
 program SurfplotGUI 
 use modSurfplotDemo 

   x(1)=0;x(2)=1 
   y(1)=0;y(2)=1 

   i = winio@  ('%ww&')                                            ! change the style of a window 
   call winop@ ('%pl[native,x_array,N_GRAPHS=1]') 
   call winop@ ('%pl[scale=linear]') 
   call winop@ ('%pl[x_min=0.,x_max=1.,y_min=0.,y_max=1.]') 
    
   i = winio@  ('%`bg[#ffffdd]&')                                  ! Background colour 
   i = winio@  ('%sf&')                                            ! return to the standard font 
   i = winio@  ('%ts&', 2d0)                                       ! set the text size 
   i = winio@  ('%bf&')                                            !  bold font 
   i = winio@  ('%es&')                                            ! close when the Escape key is pressed 

   call winop@ ('%pl[framed,axes_pen=3,width=3,x_axis='Length (um)',y_axis='Width (um)']') 

   i = winio@  ('%pv&')                                            ! allow certain controls to be re-sized under user control 

!--REMOVED   i = winio@  ('%pl&',900,600,2,x,y)! ,cb_Surfplot_plotting )  
   i = winio@('%gr[white, rgb_colours]%ff&',800,600 ) !--ADDED

   i = winio@  ('%ff&')                                            ! Form feed. To move down to below any existing controls 
   i = winio@  ('%sf&')                         
   i = winio@  ('%ts&', 1d0)                                       ! text size 
   i = winio@  ('%cn&')                                            ! centre text and controls
   i = winio@  ('%^bt[Surfplot]&',  cb_Surfplot_plotting)          
   i = winio@  ('%ff&')                
   i = winio@  ('%hw', handle)   

 end Program SurfplotGUI
30 Oct 2017 9:41 #20597

I don't know. At a quick glance neither is using smoothing (GDI+).

30 Oct 2017 11:00 #20599

Paul - and all - seems to be a flurry of activity today! Thanks for the news about [stacked].

Yes, a TYPE array could help a lot - though not clear to me how you can code symbol type, size, and colour into a single array.

Is there any documentation of all the latest features and options that you've added recently? Or will that come with the next release?

31 Oct 2017 4:30 #20605

Anyone has an idea how to do clear screen to wipe out previously made plot in native %PL like in the last example in this thread? If use %gr method instead of %pl the clear_screen@ works OK.

31 Oct 2017 4:50 #20607

There may be a way to use clear_screen@ with %pl. If not then this works...

      WINAPP
      MODULE mydata
        USE clrwin
        INTEGER,PARAMETER::n=1000,link_none=0,link_lines=1,link_curves=2
        INTEGER,PARAMETER::all_graphs=0,graph1=0
        LOGICAL shown
        DOUBLE PRECISION y(n)
      CONTAINS
      INTEGER FUNCTION show()
        INTEGER errstate
        errstate = change_plot_int@(0,'link',graph1,link_curves)
        if(errstate /= 0) print*, clearwin_string@('ERROR_REPORT')
        errstate = change_plot_int@(0,'colour',graph1,RGB@(255,0,0))
        errstate = change_plot_dbl@(0,'y_max',all_graphs,1.5d0)
        shown = .true.
        CALL simpleplot_redraw@()
        show = 2
      END FUNCTION show
      INTEGER FUNCTION clear()
        INTEGER errstate
        errstate = change_plot_int@(0,'link',graph1,link_none)
        shown = .false.
        CALL simpleplot_redraw@()
        clear = 2
      END FUNCTION clear
      INTEGER FUNCTION legend()
        IF(shown) THEN
          CALL draw_characters@('Legend:..', 300, 100, 0)
          CALL draw_line_between@(300,120,360,120,RGB@(0,0,255))
        ENDIF
        legend = 2
      END FUNCTION legend
      END MODULE mydata
      
      PROGRAM main
      USE mydata
      INTEGER i,x
      DOUBLE PRECISION p1,p2,p3,z
      !read*,i
      p1=1.5d0
      p2=150.0d0
      p3=15d0
      x=0
      DO i=1,n
        z=p1*sin(x/p3)*exp(-x/p2)
        !print*, i-1,x,z
        y(i) = z
        x=x+1
      ENDDO
      shown = .false.
      i=winio@('%ww[no_border]%ca[Damped wave]%pv&')
      i=winio@('%mn[Edit[Show, Clear]]&', show, clear)
      i=winio@('%fn[Tahoma]&')
      i=winio@('%ts&', 1.1d0)
      i=winio@('%tc&',rgb@(0,0,80))
      i=winio@('%it&')
      i=winio@('%`bg&',rgb@(230,255,225))
      CALL winop@('%pl[native,gridlines]')
      CALL winop@('%pl[title='Sample plot']')
      CALL winop@('%pl[x_axis=Time(Milliseconds)]')
      CALL winop@('%pl[y_axis=Amplitude]')
      CALL winop@('%pl[smoothing=4]') ! anti-aliasing
      CALL winop@('%pl[link=none]')   ! delay drawing
      !CALL winop@('%pl[scale=log_linear]')
      i=winio@('%^pl',500,400,n,0.0d0,1.0d0,y,legend)
      END
1 Nov 2017 2:08 #20619

Thanks, Paul,

  1. this native %pl-specific approach works

errstate = change_plot_int@(0,'link',graph1,link_none) CALL simpleplot_redraw@()

but just the clear_screen@ does not

  1. Also, while draw_ellipse@ works the draw_polygon@ seems does not with the /64
1 Nov 2017 2:37 #20621

Dan

I will take a look at clear_screen@

I can't find draw_polygon@. There is draw_polyline@.

Please login to reply.