Silverfrost Forums

Welcome to our forums

Native %pl

22 Sep 2017 1:25 (Edited: 22 Sep 2017 1:30) #20287

Not sure where to post this. I have been using the latest DLLs no 13, and playing about with the new native %pl with a view towards using it to update data plots as a simulation progresses. The following code reveals some issues.

module data_mod
implicit none
integer, parameter       :: dp = SELECTED_REAL_KIND(15,307)
integer, parameter       :: npts_max = 10000
integer                  :: npts = 2000, npts_now(2) = 0
real(kind=dp)            :: x(npts_max) = 0.d0, y(npts_max) = 0.d0, xend=0.d0, yend=0.d0
real(kind=dp), parameter :: pi = 3.1415926535897932d0
real(kind=dp), parameter :: two_pi = 2.d0*pi
real(kind=dp)            :: len = 1.d0
real(kind=dp)            :: ang = 0.0123d0
end module data_mod


module calc_mod
use data_mod
implicit none
contains
integer function build_gui()
include<windows.ins>
integer i
npts_now = 0
len=1.d0          !#### NEEDED WHEN complied in 64bit mode
i = winio@('%mn[Exit]&','exit')
i = winio@('%bg[grey]&')
i = winio@('%7.1ob&')
i = winio@('%ws&','Number of points')
i = winio@('%cb&')
i = winio@('%il&', 0, npts_max)
i = winio@('%rd&',npts)
i = winio@('%cb&')
i = winio@('%ws&','Length')
i = winio@('%cb&')
i = winio@('%rf&',len)
i = winio@('%cb&')
i = winio@('%ws&','Angle increment')
i = winio@('%cb&')
i = winio@('%rf&',ang)
i = winio@('%cb&')
i = winio@('%^tt[Plot]&',plot)
i = winio@('%cb&')
i = winio@('%ff&')
  
call winop@('%pl[native]')
call winop@('%pl[smoothing=4]')
CALL winop@('%pl[width=1]') 
CALL winop@('%pl[x_array]') 
call winop@('%pl[independent]')
call winop@('%pl[N_GRAPHS=2]')
CALL winop@('%pl[link=lines]') 
CALL winop@('%pl[colour=blue,colour=red]')
call winop@('%pl[symbol=0,symbol=11]') 
call winop@('%pl[pen_style=0]')
i = winio@('%`bg[white]&')
i = winio@('%pl&',650,600,npts_now,x,y,xend,yend)
i = winio@('%ff')
build_gui = 1
end function build_gui

integer function plot()
include<windows.ins>
integer i, counter
real(kind=dp) ang_last  
write(6,*) 'Beginning FUNCTION PLOT'
x(1) = 0.d0 ; y(1) = 0.d0 ; xend = 0.d0 ; yend = 0.d0
ang_last = 0.d0
counter = 0
do i = 2, npts
         ang_last = ang_last + ang*real(i,kind=dp)
         if (ang_last .gt. two_pi) ang_last = ang_last - two_pi
         if (ang_last .lt. two_pi) ang_last = ang_last + two_pi
         x(i) = x(i-1) + len*cos(ang_last)
         y(i) = y(i-1) + len*sin(ang_last)
         npts_now(1) = i
         npts_now(2) = 1
         xend = x(i)
         yend = y(i)
         counter = counter + 1
         if (counter .eq. 5 )then
           call YIELD_PROGRAM_CONTROL@(Y_TEMPORARILY)
           call simpleplot_redraw@()
           counter = 0
         end if
end do
write(6,*) 'Completed FUNCTION PLOT'
plot = 1
end function plot

end module calc_mod

program main
use calc_mod
implicit none
integer i
  i = build_gui()
end program main
22 Sep 2017 1:29 #20288

/cont

When complied with the 32 bit complier, strange things happen with the x and y scales.

Set Number of points to 5000, length = 1 and observe the y axis at the end of the run. Set Number of points to 7000, length = 1 and observe the y axis at the end of the run. Different even although the extents of the y axis data has not changed. Set Number of points to 5000, length = 10 and observe the x axis data at the end of the run. Note the value display at X=100.

These only occur when compiled with the 32 bit compiler - 64 bit is fine, BUT without the

len=1.d0   

line at the beginning of the function build_gui, the 64 bit program plots nothing as the initial value of len specified in the module data_mod is not picked up.

22 Sep 2017 1:33 #20289

/cont

Some pictures:-

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

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

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

22 Sep 2017 3:48 (Edited: 23 Sep 2017 11:05) #20293

Quoted from Kenneth_Smith 64 bit is fine, BUT without the

len=1.d0   

line at the beginning of the function build_gui, the 64 bit program plots nothing as the initial value of len specified in the module data_mod is not picked up.

Here is a simplified test code for reproducing this problem.

module data_mod 
implicit none 
real :: len = 1.d0 
end module data_mod

module calc_mod
use data_mod
contains
integer function build_gui() 
   print *,'len = ',len 
   build_gui = 1 
end function build_gui 

end module calc_mod 

program main 
use calc_mod 
implicit none 
integer i 
  i = build_gui() 
end program main 

The program prints 1.00000 without /64 and 0.00000 with /64. If the variable 'len' is changed to something else, such as 'xlen', the problem goes away. Perhaps the variable 'len' is confused with the intrinsic string length function?

P.S. May I highlight the fact that this bug (failure to honour initialisation of module variable) is a compiler bug and quite independent of Clearwin64 and graphical output? I am sure that Paul recognises this point, but this post is in the ClearWin+ forum and most of this thread is about graphics, so I felt that I needed to stress the point.

22 Sep 2017 11:01 #20296

John,

I forgot to mention the flicker, which is slightly irritating.

I guess Paul will read this in despair and remind us that users will always find faults, and we are all trying to plot different data over widely different ranges, but clearly the algorithm for selecting the scales needs improved. I know from my own experience that automatic selection of scales and format codes is difficult - caused me a lot of grief over the years with my own plotting routines - there's always some data that breaks the algorithm and I end up looking at ******!

These loci, which have fascinated me for many years are Euler Spirals.

Ken

23 Sep 2017 7:22 #20297

By today's standards, the original 32 bit %pl does not produce polished results and my aim was to port it to 64 bits. I am limited by a) starting from an existing interface and b) other demands on my time.

I am pleased that the native %pl is being used and that it often produces results that can be published in professional journals. At the same time I have to avoid the 'black hole' of continual improvements.

Initially I did not contemplate log-log scales with data from a random number generator with values out of range but the native %pl now has a reasonable go at it.

Making the tick marks and values always right for various scalings and fonts is unfortunately beyond my capacity in the time at my disposal. So for some data and some purposes the native %pl may not be good enough.

Having said all of that I am grateful to Ken and mecej4 for reporting bugs that should be easy to fix.

23 Sep 2017 12:41 #20298

Paul, the new %pl is a great addition. I am beginning to see more ways to use it in interactive programs and it removes one on the primary reasons I have a tendency towards procrastination. Hopefully the forum collective will not identify too many bugs but post some good working examples.

Thanks for your efforts. It is appreciated.

Ken

25 Sep 2017 7:44 #20307

John

The maximum number of plots on one graph is 10, otherwise you should get an error report. There is no programmed limit on the number of points that you can plot, memory is allocated on demand.

I don't have a quick answer to your 2nd question.

26 Sep 2017 6:05 #20314

In one sense yes, it's just a parameter in the library. But it is a static value that means that the base memory for all calls to %pl would be increased. No doubt the model can be changed but that would require a redesign and off hand I don't know how much work that would entail.

26 Sep 2017 10:30 #20316

I have to agree with John, the maximum I have used so far is N_GRAPHS=9, and I was blissfully unaware of this limitation, until now.

To me the beauty of the new %pl is the ability to display data without having to resort to exporting text files for import to excel (or equivalent) which is all time consuming, particularly where the user needs to view the plots, before the next step of an ongoing calculation. The alternative is to plot the data using %gr - which is equally time consuming to get right first time - and would be a backwards step considering all the functionality that's been built into the native %pl.

One for the wish-list which hopefully Paul will start compiling and work through - time permitting.

26 Sep 2017 11:02 #20317

Ken

I have added the option [external_ticks]. This implies [framed] and puts the tick marks externally to the frame.

26 Sep 2017 12:00 #20319

Thanks Paul, I knew you had a wish list ! 😉 Look forward to the next dll coming out.

John, One way to overcome the N_Graphs=10 limit, might be to use the %pl call back function to overlay additional graphs, in which case the GET_PLOT_POINT@ subroutine would provide all the required geometric data. Just a thought. I will try this when I have time.

27 Sep 2017 9:49 #20327

Paul, Another one for you to look at I am afraid.

The following code plots two points on the x-y plane. Note that there is a spin wheel on one of the Y values. Running the program and increasing this Y value incrementally reveals some issues.

When compiled under 32 bit, for the following Y values the corresponding point is not plotted 4.5, 9.0, 11.5, 14.5, 15.5, 18.0, 18.5, 20.5, 23.0 etc.

When compiled under 64 bit, this still happens, but it first occurs for a Y value of 48.5, then 80.5, 83.5 etc.

I am using the most recent DLLS (13).

module geometry
implicit none
integer, parameter :: dp = SELECTED_REAL_KIND(15,307)
integer, parameter :: n_ew_max  = 2
real(kind=dp)      :: ew_cond_coords_x(1:n_ew_max)       = (/1.d0,2.d0/)
real(kind=dp)      :: ew_cond_coords_y(1:n_ew_max)       = (/1.d0,2.d0/)

contains

  integer function get_geometry()
  include<windows.ins>
  integer i
    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    i = winio@('%nl%3.3ob[scored]&')
    i = winio@('%cb&')
    i = winio@('%ws&','X [m]')
    i = winio@('%cb&')
    i = winio@('%ws&','Y [m]')
    i = winio@('%cb&')

    i = winio@('%ws&','1')
    i = winio@('%cb&')
    i = winio@('%^rf&',ew_cond_coords_x(1), update_graphics)
    i = winio@('%cb&')
    i = winio@('%df&', 0.5d0)
    i = winio@('%^rf&',ew_cond_coords_y(1), update_graphics)
    i = winio@('%cb&')

    i = winio@('%ws&','2')
    i = winio@('%cb&')
    i = winio@('%^rf&',ew_cond_coords_x(2), update_graphics)
    i = winio@('%cb&')
    i = winio@('%^rf&',ew_cond_coords_y(2), update_graphics)
    i = winio@('%cb&')
    
    call winop@('%pl[native]')
    CALL winop@('%pl[width=2]') 
    CALL winop@('%pl[x_array]') 
    call winop@('%pl[N_GRAPHS=1]')
    CALL winop@('%pl[link=none]') 
    CALL winop@('%pl[colour=blue]')
    call winop@('%pl[symbol=11]') 
    call winop@('%pl[pen_style=0]')
    call winop@('%pl[y_min=0]')
    i = winio@('%`bg[white]&')
    i = winio@('%pl', 500, 500, 2, ew_cond_coords_x, ew_cond_coords_y)
    get_geometry = 1

  end function get_geometry

  integer function update_graphics()
  include<windows.ins>
    call simpleplot_redraw@()
    update_graphics=1
  end function update_graphics
  
end module geometry

program main
use geometry
implicit none
integer i
i = get_geometry()
end program main

If I change [link=none], to [link=lines], the line joining the points is correctly drawn.

I have a work around - essentially finding the maximum y value and plotting an invisible graph that has its maximum slightly larger (x 1.01 which works for this data set, x 1.001 does not).

27 Sep 2017 11:49 #20328

John, this might help.

module keraunic_mod
implicit none
integer, parameter              :: dp = SELECTED_REAL_KIND(15,307)
real(kind=dp), allocatable :: x_td(:), y_ng(:)
contains
  real(kind=dp) function keraunic_to_ng(td)
  real(kind=dp), intent(in) :: td
    if (td .lt. 0.d0) then
      keraunic_to_ng = 0.d0
    else
      keraunic_to_ng = 0.04d0*td**1.25d0
    end if
  end function keraunic_to_ng

  integer function view_keraunic_data()
  include<windows.ins>
  integer, parameter :: td_max = 350
  integer i
    allocate(x_td(1:td_max), y_ng(1:td_max))
    do i = 1,td_max, 1
      x_td(i) = real(i,kind=dp)  ; y_ng(i) = keraunic_to_ng(real(i,kind=dp))
    end do  
    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    call winop@('%pl[native,smoothing=4,framed,etched,width=2]') 
    CALL winop@('%pl[x_array,N_GRAPHS=1,link=lines,colour=black]')
    call winop@('%pl[symbol=0,pen_style=0]')
    call winop@('%pl[title='Ground Flash Density Ng Vs. Keraunic level Kd']')
    call winop@('%pl[x_axis='Thunderstorm Td [days/year]']')
    call winop@('%pl[y_axis='Ground flash density Ng [flashes/sq.km]']')
    i = winio@('%`bg[white]&')
    i = winio@('%^pl&',700,600,td_max,x_td,y_ng,caption_cb)
    i = winio@('%ff')
    deallocate(x_td, y_ng)
    view_keraunic_data = 1
  end function view_keraunic_data

  integer function caption_cb()
  include<windows.ins>
  real(kind=dp) x, y, xpix, ypix
    call SELECT_FONT@('tahoma') 
!   London 18 thunderstorm days per year
    x = 18.d0 ; y = keraunic_to_ng(x)
    call GET_PLOT_POINT@(x,y,xpix,ypix)
    call draw_filled_ellipse@(int(xpix),int(ypix),3,3,rgb@(0,0,255))
    call draw_characters@('London',int(xpix) + 5, int(ypix) - 150,rgb@(0,0,255))
    call draw_line_between@(int(xpix),int(ypix),int(xpix) + 5, int(ypix) - 150  ,rgb@(0,0,255))
!   Las Vegas    
    x = 13.d0 ; y = keraunic_to_ng(x)
    call GET_PLOT_POINT@(x,y,xpix,ypix)
    call draw_filled_ellipse@(int(xpix),int(ypix),3,3,rgb@(0,0,255))
    call draw_characters@('Las Vegas',int(xpix) + 5, int(ypix) - 170 ,rgb@(0,0,255))
    call draw_line_between@(int(xpix),int(ypix),int(xpix) + 5, int(ypix) - 170  ,rgb@(0,0,255))
!   HONOLULU, 7
    x = 7.d0 ; y = keraunic_to_ng(x)
    call GET_PLOT_POINT@(x,y,xpix,ypix)
    call draw_filled_ellipse@(int(xpix),int(ypix),3,3,rgb@(0,0,255))
    call draw_characters@('Honolulu',int(xpix) + 5, int(ypix) - 210 ,rgb@(0,0,255))
    call draw_line_between@(int(xpix),int(ypix),int(xpix) + 5, int(ypix) - 210  ,rgb@(0,0,255))
    caption_cb = 1
  end function caption_cb
end module keraunic_mod

program main
use keraunic_mod
i=view_keraunic_data()
end program main
4 Oct 2017 6:36 #20366

I missed this post. You've got a lot of progress!

I am surprised that Mecej4, John Campbell, Eddie and other power users completely missed %pl. The progress to make it much more functional would go faster then. You guys don't plot anything during the run? And don't need debugging sometimes your data? The plotting a graph and look at data would take one single line, almost as short as with the write(,) variable (i,j), i=1,n),j=1,m) when you debug with the help of %pl.

5 Oct 2017 10:46 #20381

I have been experimenting with log_log scales.

module relay_curves_mod
implicit none

integer, parameter, private :: dp = SELECTED_REAL_KIND(15,307)
integer, parameter :: npts=60000
real(kind=dp) :: stand_inv(1:npts) = 0.d0, very_inv(1:npts) = 0.d0, extreme_inv(1:npts) = 0.d0, &
                 long_time_inv(1:npts) = 0.d0, amps(1:npts) = 0.d0

contains
  real(kind=dp) function trip_time(char_type, is, i, tms)
  integer, intent(in)       :: char_type  !Integer to denote characteristics
  real(kind=dp), intent(in) :: is         !Setting  current
  real(kind=dp), intent(in) :: i          !Fault current
  real(kind=dp), intent(in) :: tms        !Time multiplier setting
  real(kind=dp), parameter :: alpha(1:4) = (/0.02d0,1.d0,2.d0,1.d0/)
  real(kind=dp), parameter :: k(1:4) = (/0.14d0,13.5d0,80.d0,120.d0/)
    trip_time = 0.d0
    if (char_type .gt. 4) return
    if (char_type .lt. 1) return
    if ( (((i/is)**alpha(char_type)) - 1.d0 ) .gt. 0.d0 ) then
      trip_time = ( k(char_type)/ ( ((i/is)**alpha(char_type)) - 1.d0 ) ) * tms
    end if
  end function trip_time

  integer function generate_curves()
  include<windows.ins>
  integer i
  real(kind=dp) amp, min_y
    amp = 1.005d0
    do i = 1, npts
      stand_inv(i)     = trip_time(1, 1.d0, amp, 1.d0)
      very_inv(i)      = trip_time(2, 1.d0, amp, 1.d0)
      extreme_inv(i)   = trip_time(3, 1.d0, amp, 1.d0)
      long_time_inv(i) = trip_time(4, 1.d0, amp, 1.d0)
      amps(i)          = amp
      amp = amp+0.01d0
    end do
    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    i = winio@('%ts&', 1.5d0)
    call winop@('%pl[native,smoothing=4,framed,etched,width=2]') 
    CALL winop@('%pl[x_array,N_GRAPHS=4]')
    call winop@('%pl[scale=log_log]')
!    call winop@('%pl[y_min=0.0001, y_max=10000]') 
!    call winop@('%pl[x_min=1,    x_max=1000]')
    call winop@('%pl[link=lines, colour=black,symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=blue, symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=red,  symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=green,symbol=0, pen_style=0]')
    call winop@('%pl[title='STANDARD IEC IDMT CHARACTERISTICS']')
    call winop@('%pl[x_axis='Multiple of setting current [-]']')
    call winop@('%pl[y_axis='Relay operating time [s]']')
    i = winio@('%`bg[white]&')
    i = winio@('%pl',800,600,npts,amps,stand_inv,very_inv,extreme_inv,long_time_inv)
    generate_curves = 1
  end function generate_curves
end module relay_curves_mod

program main
use relay_curves_mod
integer i
i = generate_curves()
end program main
5 Oct 2017 11:17 #20382

The code above produces:-

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

Adding

    call winop@('%pl[y_min=0.0001, y_max=10000]') 
    call winop@('%pl[x_min=1,    x_max=1000]')

Gives me:-

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

Now apart from the position of the y axis label and the lack of grid lines this is almost a perfect graph for my purposes. I assume, but have yet to test, that y_min, y_max etc can be changed via the %pl call back function, after scanning the data arrays to find the min and max vals to set the y_min etc values to a value corresponding to 10**N where N is an integer, so that the range covers the values to be plotted. Setting y_min = 0.00022 in the first plot above makes no sense to me, surely y_min = 0.0001 is better?

5 Oct 2017 11:22 #20383

NOTE, the two plots above were produced using DLL14 and 64 bit. When using 32 bit, the modified code for the second plot has a problem with the y-axis.

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

The label values at 10-3 and 10-4 appear as 0.

6 Oct 2017 10:27 #20384

A slightly modified version of last night's code. By scanning the data arrays before the call to %pl in order to set the plot limits we can get it right first time for this type of data set.

module relay_curves_mod
implicit none

integer, parameter, private :: dp = SELECTED_REAL_KIND(15,307)
integer, parameter :: npts=60000
real(kind=dp) :: stand_inv(1:npts) = 0.d0, very_inv(1:npts) = 0.d0, extreme_inv(1:npts) = 0.d0, &
                 long_time_inv(1:npts) = 0.d0, amps(1:npts) = 0.d0

contains
  real(kind=dp) function trip_time(char_type, is, i, tms)
  integer, intent(in)       :: char_type  !Integer to denote characteristics
  real(kind=dp), intent(in) :: is         !Setting  current
  real(kind=dp), intent(in) :: i          !Fault current
  real(kind=dp), intent(in) :: tms        !Time multiplier setting
  real(kind=dp), parameter :: alpha(1:4) = (/0.02d0,1.d0,2.d0,1.d0/)
  real(kind=dp), parameter :: k(1:4) = (/0.14d0,13.5d0,80.d0,120.d0/)
    trip_time = 0.d0
    if (char_type .gt. 4) return
    if (char_type .lt. 1) return
    if ( (((i/is)**alpha(char_type)) - 1.d0 ) .gt. 0.d0 ) then
      trip_time = ( k(char_type)/ ( ((i/is)**alpha(char_type)) - 1.d0 ) ) * tms
    end if
  end function trip_time

  integer function generate_curves()
  include<windows.ins>
  integer i
  real(kind=dp) amp
  real(kind=dp) :: min_y, max_y, min_x, max_x
  character(len=240) min_y_ch, max_y_ch, min_x_ch, max_x_ch
    amp = 1.005d0
    do i = 1, npts
      stand_inv(i)     = trip_time(1, 1.d0, amp, 1.d0)
      very_inv(i)      = trip_time(2, 1.d0, amp, 1.d0)
      extreme_inv(i)   = trip_time(3, 1.d0, amp, 1.d0)
      long_time_inv(i) = trip_time(4, 1.d0, amp, 1.d0)
      amps(i)          = amp
      amp = amp+0.01d0
    end do
6 Oct 2017 10:30 #20385

cont

    i = winio@('%mn[Exit]&','exit')
    i = winio@('%fn[Tahoma]&')
    i = winio@('%ts&', 1.5d0)
    call winop@('%pl[native,smoothing=4,framed,etched,width=2]') 
    CALL winop@('%pl[x_array,N_GRAPHS=4]')
    call winop@('%pl[scale=log_log]')
    
!   ------------------------------------------------    
    min_x = minval(amps)
    max_x = maxval(amps)
    min_y = min( minval(stand_inv), minval(very_inv), minval(extreme_inv), minval(long_time_inv))
    max_y = max( maxval(stand_inv), maxval(very_inv), maxval(extreme_inv), maxval(long_time_inv))
    call winop@('%pl[y_min='//trim(log10scale_min_char(min_y))//']') 
    call winop@('%pl[y_max='//trim(log10scale_max_char(max_y))//']')
    call winop@('%pl[x_min='//trim(log10scale_min_char(min_x))//']') 
    call winop@('%pl[x_max='//trim(log10scale_max_char(max_x))//']') 
!   ---------------------------------------------------
     
    call winop@('%pl[link=lines, colour=black,symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=blue, symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=red,  symbol=0, pen_style=0]')
    call winop@('%pl[link=lines, colour=green,symbol=0, pen_style=0]')
    call winop@('%pl[title='STANDARD IEC IDMT CHARACTERISTICS']')
    call winop@('%pl[x_axis='Multiple of setting current [-]']')
    call winop@('%pl[y_axis='Relay operating time [s]']')
    i = winio@('%`bg[white]&')
    i = winio@('%pl',800,600,npts,amps,stand_inv,very_inv,extreme_inv,long_time_inv)
    generate_curves = 1

    contains
Please login to reply.