Silverfrost Forums

Welcome to our forums

Native %pl

6 Oct 2017 10:31 #20386

cont

    character(len=120) function log10scale_max_char(max_val)
    real(kind=2), intent(in) :: max_val
    real(kind=2) scale_max
      scale_max = log10scale_max(max_val)
      write(log10scale_max_char,*) scale_max
    end function log10scale_max_char


    character(len=120) function log10scale_min_char(min_val)
    real(kind=2), intent(in) :: min_val
    real(kind=2) scale_min
      scale_min = log10scale_min(min_val)
      write(log10scale_min_char,*) scale_min
    end function log10scale_min_char

    real(kind=2) function log10scale_max(max_val)
    real(kind=2), intent(in) :: max_val
    integer i
    real(kind=2) test_val
      do i = 308, -308, -1
        test_val = 10.d0**i
        if (max_val .gt. test_val) then
          log10scale_max = 10.d0**(i+1)
          exit
        else if (max_val .eq. test_val) then
          log10scale_max = test_val
          exit
        end if
      end do
    end function log10scale_max

    real(kind=2) function log10scale_min(min_val)
    real(kind=2), intent(in) :: min_val
    integer i
    real(kind=2) test_val
      do i = -308, 308, 1
        test_val = 10.d0**i
        if (min_val .lt. test_val) then
          log10scale_min = 10.d0**(i-1)
          exit
        else if (min_val .eq. test_val) then
          log10scale_min = test_val
          exit
        end if
      end do
    end function log10scale_min
    
  end function generate_curves
  
end module relay_curves_mod

program main
use relay_curves_mod
integer i
i = generate_curves()
end program main
6 Oct 2017 10:36 #20387

cont

This works ok with DLL14 64 bit.

6 Oct 2017 3:05 #20391

Based on how much source text takes to plot similar graphs in Matlab or even older Simpleplot PL, i'd say that the glorious times of hacking returned back to this forum 😃. Before this was with broken Simpleplot PL, now it's native PL.

After trying everything we still could not fix the LOG_LOG with older Simpleplot PL, it worked only if X values do not exceed 1. And it had no X_min, Y_min, or framed plotting, and was buggy, crashing at Y values > 1e22, crashing debugger, not working with 64bit etc.

But like Matlab, older Simpleplot PL had no big problems with the correct LOG tics or labels. And, like in Matlab, the whole source code for the similar plots like above take only one single source text line. If it would take more no one would use them. With Matlab even 3D plot is done with one line, clearly people at Matlab know human psychology very well.

Here is what older Simpleplot PL produced (though crashing inside with LOG_LOG and turning to LINEAR_LOG plotting instead) with just one-two lines of Fortran code if plotting data already exist and all the fonts were preliminary set up. No minimum/maximum beautifications were necessary, let alone using Y_min for the native PL fixing. This is one single 132 character Fortran line!

i=winio@('%pl[title='STANDARD CHARACTERISTICS',colour=red,colour=green,X_ARRAY,N_GRAPHS=3,SCALE=LOG_LOG]%es',640,480,5,X,Y1,Y2,Y3)

https://s25.postimg.org/4w58sezdb/Simpleplot.jpg

The whole source code with setting data and fonts is here, SLINK its obj file with SIMPLE.DLL

real*8, dimension (5) :: X  = (/1.,    20.,  60., 200., 600./) 
real*8, dimension (5) :: Y1 = (/2.9e4, 300.,  3., 0.2,  0.0022/) 
real*8, dimension (5) :: Y2 = (/2.5e4, 500.,  2., 0.4,  0.042/) 
real*8, dimension (5) :: Y3 = (/2.2e4, 722.,  2., 0.5,  0.072/) 

        CALL DIAGLV (0)        
        CALL TEXTMN(0.4)      ! setting font size
        CALL AXLBJS('*C','C')  ! centering tic labels
        call thckmg('LINE',4.)  ! setting line width
        call chset(-11)          ! setting fonts

!... Case of two lines of Fortran source code
i=winio@('%ww%pv%pl[title='STANDARD IEC IDMT CHARACTERISTICS', x_axis='Multiple of setting current',y_axis='Relay operating time&
& [s]',  colour=red, colour=blue, colour=green, X_ARRAY, N_GRAPHS=3, SCALE=LOG_LOG]%es', 640, 480, 5, X, Y1, Y2, Y3)

End

Times actually are coming that even one single line will be way too much. People take their data to cell phone graphics plotting utility which costs $1 or is even free, set there all the MINs and MAXs if needed, and all analysis is done without programming at all. Look at BridPlot for example, the grand-grandson of Simpleplot.

7 Oct 2017 9:51 #20400

Dan's data combined with Friday's 'hack' and I can replicate the performance of the old simple plot with the native %pl.

http://www.tr5mx.co.uk/pl001.jpg

And it works for log_log scales.

http://www.tr5mx.co.uk/pl002.jpg

7 Oct 2017 1:46 #20402

I was going to add grid lines to my log_log plots but unfortunately get_plot_point@ does not work with log scales as this example demonstrates.

module test
implicit none
integer, parameter, private :: dp = SELECTED_REAL_KIND(15,307)
real(kind=dp) :: x(1:5) = (/0.1d0,1.d0,10.d0,100.d0,1000.d0/)
real(kind=dp) :: y(1:5) = (/0.1d0,1.d0,10.d0,100.d0,1000.d0/)

contains

  integer function plot()
  include<windows.ins>
  integer i
    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    i = winio@('%ts&', 1.5d0)
    call winop@('%pl[native,x_array,N_GRAPHS=1]')
    call winop@('%pl[scale=log_log]')
    call winop@('%pl[y_min=0.1,y_max=1000,x_min=0.1,x_max=1000]')
    call winop@('%pl[link=curves, colour=blue, symbol=11, pen_style=0]')
    i = winio@('%`bg[white]&')
    i = winio@('%^pl',800,600,5,x,y,call_back)
    plot=1
  end function plot

  integer function call_back()
  include<windows.ins>
  real(kind=dp) xx, yy
  integer i
    do i = 1, 5
      call get_plot_point@(x(i), y(i), xx, yy)
      call draw_ellipse@(nint(xx),nint(yy),6,6,rgb@(0,0,0))
      write(6,*) x(i), y(i), nint(xx), nint(yy)
    end do  
    call_back = 1
  end function call_back
  
end module test

program main
use test
integer i
i = plot()
end program main
7 Oct 2017 4:19 #20404

As everyone can see from comparison, even after the tricks and beautifications, even though the curves in native PL look better then in older PL, the unreasonable frame numbering, wrongly placed tic marks and other errors making the whole plot far from production quality.

Without the tricks (of setting X and Y axis min and max at exact orders of magnitude as Ken have done above) and beautifications (bullets, frames, font and lines sizes), here is what novice user will see for the first time in native PL as a default image when he will visualize with LOG_LINEAR and LOG_LOG the data above (even using more lines of Fortran code). For everyone raised on shiny covers of journals and flashy websites the cultural shock is guaranteed:

use clrwin
real*8 :: X (5) = (/1.,    20.,  60., 200., 600./) 
real*8 :: Y1(5) = (/2.9e4, 300.,  3., 0.2,  0.0022/) 
real*8 :: Y2(5) = (/2.5e4, 500.,  2., 0.4,  0.042/) 
real*8 :: Y3(5) = (/2.2e4, 722.,  2., 0.5,  0.072/) 

i=winio@('%pl[title='STANDARD IEC IDMT CHARACTERISTICS', x_axis='Multiple of setting current',y_axis='Relay operating time&
& [s]',  colour=red, colour=blue, colour=green, X_ARRAY, N_GRAPHS=3, SCALE=LOG_LOG]%es', 720, 480, 5, X, Y1, Y2, Y3)

End

https://s25.postimg.org/gaa5mn0v3/My_Native_PL_LOG_Linear.jpg https://s25.postimg.org/4xxk4yfcf/My_Native_PL_LOG_LOG.jpg

Just in case, the compilation: ftn95 NativePL.f95 /link /64

8 Oct 2017 10:46 #20406

I do agree with you Dan, my perseverance and enthusiasm with native the %pl is beginning to falter somewhat. I have hoped to be able to generate a plot similar to the one below with grid lines, but it's not that straightforward. Even if I can decode the coordinates returned by get_plot_point@ with log graphs, there is an added complication of user selected margins to consider, which takes me back to the struggles I have with my own %gr based plotting routines.

http://tr5mx.co.uk/idmt.jpg

Guess we all just have to wait on Paul and his colleagues having the time to look at these issues. A quick fix for get_plot_point@ with log scales would be a step in the right direction as I can live with having to select appropriate ranges for scales.

12 Oct 2017 6:03 #20409

I don't know if it is a bug or if, like a number of these plots, it is a matter of choosing nice values for y_min, y_max, dx and dy. If and when I am able to do more work on this we will need to start off with some simple plots that illustrate the problems. But please don't post them now.

In the mean time one or two fixes have been made and...

  1. the limit on number of plots (previously 10) has been removed. At the same time, an option [stacked] has been added which means that the y (and x) data for different plots is concatenated in order to avoid multiple winio@ arguments. The concatenation is equivalent to using a two dimensional array for the data but this 2D array can be 'ragged'.

  2. an option [gridlines] has been added with the expected result.

12 Oct 2017 11:40 #20410

Paul,

The option external_ticks works well, but unfortunately it does not address the issue of cases where the data to be plotted obscures the scale numbers on the axis as shown bottom right below, perhaps you might consider an 'external_scales' option at some time in the future.

http://www.tr5mx.co.uk/external_ticks.jpg

Apologies for raising this again, my intention is to provide positive suggestions which all users will benefit from rather than negative feedback.

The news that you have implemented grid lines is a big step forward. I look forward to being able to use that option.

12 Oct 2017 12:05 #20411

As for the issue with get_plot_point@ with log-log scales, I don't think this is related to the selection of y_min, y_max etc. I have experimented with lots of variations on this. My impression is that somewhere within %pl there is a coordinate transformation that is the root cause of all the problems we are collectively complaining about.

12 Oct 2017 1:04 #20412

Thanks Ken. I hope to come back to this thread when things are a little quieter.

12 Oct 2017 2:51 #20414

John,

My quick and dirty fix for get_plot_point@ for log_log scales with logs using base 10.

module test
implicit none
integer, parameter, private :: dp = SELECTED_REAL_KIND(15,307)
integer, parameter, private :: npts = 5
real(kind=dp) :: x(1:npts) = (/0.1d0,1.d0,10.d0,100.d0,1000.d0/)
real(kind=dp) :: y(1:npts) = (/0.1d0,1.d0,10.d0,100.d0,1000.d0/)
integer margin, gw, gh                     !############
real(kind=dp) x_min, y_min, x_max, y_max   !############
contains
  integer function plot()
  include<windows.ins>
  integer i
    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    i = winio@('%ts&', 1.5d0)
    call winop@('%pl[framed,etched]')
    call winop@('%pl[x_array,N_GRAPHS=1]')
    call winop@('%pl[margin=80]')                !#########
    margin = 80                                  !#########
    call winop@('%pl[scale=log_log]')
    call winop@('%pl[y_min=0.1,y_max=1000,x_min=0.1,x_max=1000]')
    y_min = 0.1d0                                  !##########
    y_max = 1000.d0                                !##########
    x_min = 0.1d0                                  !##########
    x_max = 1000.d0                                !##########
    call winop@('%pl[link=lines, colour=blue, symbol=11, pen_style=0]')
    i = winio@('%`bg[white]&')
    gw = 800                                     !##########
    gh = 600                                     !##########
    i = winio@('%^pl',gw,gh,npts,x,y,call_back)  !##########
    plot=1
  end function plot

  integer function call_back()
  include<windows.ins>
  real(kind=dp) xx, yy
  integer i
    do i = 1, npts
      call get_plot_point_k(x(i), y(i), xx, yy)
      call draw_ellipse@(nint(xx),nint(yy),6,6,rgb@(0,0,0))
    end do
    call_back = 1
  end function call_back

  subroutine get_plot_point_k(x,y,xx,yy)
  real(kind=dp), intent(in)  :: x, y
  real(kind=dp), intent(out) :: xx, yy
    xx    = log10(x) ; yy    = log10(y)
    xx    = map_range(log10(x_min),log10(x_max),real(margin,kind=dp),real(gw-margin,kind=dp),xx)
    yy    = map_range(log10(y_min),log10(y_max),real(gh-margin,kind=dp),real(margin,kind=dp),yy)
  end subroutine get_plot_point_k
  
  real(kind=dp) function map_range(a1, a2, b1, b2, s)
  real(kind=dp), intent(in) :: a1, a2, b1, b2, s
      map_range = (s - a1) * (b2 - b1) / (a2 - a1) + b1 
  end function map_range
  
end module test

program main
use test
implicit none
integer i
i = plot()
end program main
12 Oct 2017 2:55 #20415

and the corresponding plot

http://tr5mx.co.uk/john_log_log.jpg

15 Oct 2017 3:30 #20447

John, You can define the margins as integer variables and build up the pl string as follows before the final call to pl.

module pl_routines
implicit none
contains
  subroutine set_pl_margins(top, bottom, left, right)
  include<windows.ins>
  integer, intent(in) :: top, bottom, left, right
  character(len=5), parameter :: fmt1 = '(I5)'
  character(len=5)  t_txt, b_txt, l_txt, r_txt
  character(len=12):: start_str = '%pl[margin=('
  character(len=2 ):: end_str = ')]'
  character(len=80)   str
  write(t_txt,fmt1) top      ;  write(b_txt,fmt1) bottom
  write(l_txt,fmt1) left     ;  write(r_txt,fmt1) right
  ! Call to %pl[margin...] is left, top, right, bottom
  str = start_str//trim(adjustl(l_txt))//','&
                 //trim(adjustl(t_txt))//','&
                 //trim(adjustl(r_txt))//','&
                 //trim(adjustl(b_txt))//end_str
    write(6,*) str
    call winop@(str)    
  end subroutine set_pl_margins  
end module pl_routines

program test
use pl_routines
implicit none
include<windows.ins>
integer, parameter :: npts = 11
real(kind=2) x(1:npts), y(1:npts)
integer i, t, b, l, r
  t = 200 ; b = 200 ; l = 100 ; r = 100
  do i = 1,npts
    x(i) = i-1
    y(i) = (i-1)**2
  end do
  i = winio@('%mn[Exit]&','exit') 
  i = winio@('%fn[Tahoma]&')
  i = winio@('%ts&', 1.5d0)
  call winop@('%pl[native,x_array,N_GRAPHS=1]') 
  call winop@('%pl[y_min=0,y_max=100,x_min=0,x_max=10]')
  call winop@('%pl[link=curves, colour=blue, symbol=11, pen_style=0]')
  call set_pl_margins(t,b,l,r)   !top, bottom, left, right
  i = winio@('%`bg[white]&')
  i = winio@('%pl',600,500,npts,x,y)
end program test
15 Oct 2017 10:08 #20448

Small change of subject. I have an idea how to plot full-colour area plots rather like Dan has asked for. The only thing that prevents this is that colours are defined by names. I need to be able to use RGB values (as obtained from function RGB@). This should really not be a major problem to implement ?

I would then divide the data set into multiple sets for different value ranges and plot each with a different colour. This would need more than the very limited set of named colours, to allow the use of a full colour palette.

Of course a much neater way to do this would be to allow a separate RGB value to be associated with each X,Y pair - i.e. each point would have its own colour, so we would have 3 arrays, X,Y, RGB. Any chance of doing this ?

16 Oct 2017 12:30 (Edited: 16 Oct 2017 6:46) #20452

Silicondale, I agree, that would be good addition to Paul's reported concatenation few days back, I do not know how it was done but suspect this way

%pl(X,Y)

where X(i,j) and Y(i,j) are 2D arrays and number of plots j can be very large.

In this case adding color

%pl(X,Y,iColor)

besides expanding functionality of usual X-Y plotting will automatically turn native %pl into 2D surface plotter. But suspect this stuff will be for the future, after our usual 1D X-Y plots will be made perfect

16 Oct 2017 3:56 #20455

Ken,

I think silicondale got with your example problem with resizing.

To do resize just add %ww%pv to %pl'

i = winio@('%ww%pv%pl%es',600,500,npts,x,y) 

By some reason resizing does not work if %ww is absent. In many other cases %ww indeed is redundant (unless this is not some Clearwin bug and %ww must be always present)

In my turn I have difficulty compiling your latest posted codes because always have error

' PROCESSING MODULE [<PL_ROUTINES> FTN95/Win32 v8.10.0] *** This statement contains an illegal character - ' '' *** This statement contains an illegal character - ' '' *** This statement contains an illegal character - ' ''

Is this some kind of a celtic space of some UTF8 character coding ? 😃. Removing all spaces solves the problem.

Do others also have similar problems?

16 Oct 2017 6:35 (Edited: 6 Nov 2017 3:27) #20459

Silicondale

I am not sure if this is what you need but you can set the colour via

call winopt@('%pl[colour=#bbggrr]')

where bb is the hex value for the blue component etc.

For example:

call winopt@('%pl[colour=#FF0000]')

for blue etc.

It's a little more tricky if the colour is 'dynamic'. For example if the colour has components R,G,B then you would need something like...

        write(str,'(a,z6.6,a)') '%pl[colour=#', RGB@(B,G,R), ']'
        CALL winop@(trim(str))

because we need the reverse order to that given by RGB@.

p.s. This post is incorrect. See new post in this thread.

16 Oct 2017 7:01 #20460

Paul - many thanks for that. Certainly goes some of the way towards what we need, especially your 'dynamic colour' workaround. Ideally we should be able to attach a different colour to each individual point, but this is certainly a start. Could of course split the data into thousands of separate one-element arrays each with its own colour, but that wouldn't really be workable with %pl as it is!

By the way, I have been using winop@ but this is the first time I have seen winopt@ - can you point me to any documentation, please?

Odd that you use #bbggrr - the standard that I think is more commonly used (such as in HTML coding, for example) is #rrggbb

16 Oct 2017 7:57 #20461

winopt@ was just my typing error. It should be winop@. I am guessing that #bbggrr is somebody's standard. Is it not HTML?

Please login to reply.