forums.silverfrost.com Forum Index forums.silverfrost.com
Welcome to the Silverfrost forums
 
 FAQFAQ   SearchSearch   MemberlistMemberlist   UsergroupsUsergroups   RegisterRegister 
 ProfileProfile   Log in to check your private messagesLog in to check your private messages   Log inLog in 

New Video
Goto page Previous  1, 2, 3, 4, 5, 6  Next
 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+
View previous topic :: View next topic  
Author Message
Martin_K



Joined: 09 Apr 2020
Posts: 227

PostPosted: Sat Jun 20, 2020 9:08 pm    Post subject: Reply with quote

Thanks Ken!

Today in the afternoon I already tested also your code you provided now again, with no positive effect (my problem remains)

Currently, it looks like follows (my handle_pl=0):

Code:

INTEGER FUNCTION update_PL_limits ()    ! call-back to update the graphs
    USE CLRWIN                  
    IMPLICIT NONE
    INTEGER*4
   
ag=CHANGE_PLOT_DBL@(handle_pl,'x_min',0,y_min_now);ag=CHANGE_PLOT_DBL@(handle_pl,'x_max',0,y_max_now)
ag=CHANGE_PLOT_DBL@(handle_pl,'y_min',0,x_min_now);ag=CHANGE_PLOT_DBL@(handle_pl,'y_max',0,x_max_now)
       
!  CALL simpleplot_redraw@()
i = akt_graf ()  !contains calling to SELECT_GRAPHICS_OBJECT@(handle_pl) and SIMPLEPLOT_REDRAW@() functions
   
    update_PL_limits=1
END FUNCTION update_PL_limits


The axes are reversed in the code above due to the way how our national geodetical coordinate system is defined (but this is formal thing only)
So, investigating further, although I have such feeling that the problem may really lie hidden here (based on graphs behaviour).

Martin
Back to top
View user's profile Send private message
Martin_K



Joined: 09 Apr 2020
Posts: 227

PostPosted: Sat Jun 20, 2020 9:30 pm    Post subject: Reply with quote

I forgot to add the following:

It can be an interesting indicator, as soon as I zoom in by pressing the zoom in button, the X,Y captions dismiss (they re-appear only then, when I press zoom to extents). In any zooming in/out, they always disappear.

Currently, the code in the %PL call-back after the condition PLOT_ADJUST looks like this:

Code:

IF (cb_reason .eq. 'PLOT_ADJUST') THEN
 
       
 !       CALL SELECT_GRAPHICS_OBJECT@(handle_pl)   !výber grafu
         CALL select_font@('arial')                                   ! nový font
        CALL bold_font@(1)                                           ! bold aktivovaný       
!        CALL size_in_pixels@(15,15)                          ! výška fontu v pixeloch
        CALL size_in_points@(15,15)                          ! výška fontu v bodoch
        CALL draw_characters@('Y_S-JTSK [m]',600,630,RGB@(255,0,255))  ! napisanie textu Y_S-JTSK [m] horizontálna os - nadpis
        CALL rotate_font@(90.0d0) ! Otocenie textu (pre zvislu os (v S-JTSK je to os X a napise X_S-JTSK [m] do vertikálnej polohy)
        CALL draw_characters@('X_S-JTSK [m]',90,400,RGB@(255,0,255)) vertikalna os - nadpis
        CALL rotate_font@(0.0d0) ! spat do horizontalnej roviny


i = COPY_GRAPHICS_REGION@(handle_internal_gr, 1, 1, gw, gh, handle_pl, 1, 1, gw, gh, 13369376)    ! kópia do pamäte
 END IF


All the codes above worked problem free with previous versions of DLLs.
Back to top
View user's profile Send private message
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sat Jun 20, 2020 10:56 pm    Post subject: Reply with quote

Martin,

The %pl call back will only be called once by the pl part of the code and that is when the %pl region is initially created. This is indicated by the presence of the PLOT_ADJUST string. The captions will therefore be drawn initially correctly. Subsequent calls to SIMPLEPLOT_REDRAW@ will now no longer call the %pl call back, so the actions that previously were there triggered by the PLOT_ADJUST string have to be placed elsewhere.

Move everything that was within the

Code:
 IF (cb_reason .eq. 'PLOT_ADJUST') THEN  ;;;;;; END IF

to a new subroutine

Call this new subroutine from within the IF (cb_reason .eq. 'PLOT_ADJUST') THEN control block in the pl_cb, and also after your calls to SIMPLEPLOT_REDRAW@. With the previous DLLs the call to SIMPLEPLOT_REDRAW@ would call the pl_cb – now it does not.

If you do this it should fix your axes problem.

No changes should be necessary to any other parts of the pl_cb associated with mouse moves etc.

Paul, may have an idea why the previous limits set for the pl region now appear to get forgotten – which is a change to the way the program operated before.

I did a quick test on my previous code – the one with the buttons to pan and zoom. I added another button, the call back of which only calls simpleplot_redraw@ and the currently selected limits, after a zoom operation are not “lost”. Added another button which changes the data to be plotted, - again the call to SIMPLEPLOT_REDRAW@ associated with this does not change the plot limits. This code is below.

If you comment out all the code in the pl_cb associated with a mouse move and drawing the yellow box of coordinates does the zoom function still fail?

Ken
Back to top
View user's profile Send private message Visit poster's website
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sat Jun 20, 2020 10:58 pm    Post subject: Reply with quote

Code:

implicit none
integer, parameter :: dp = kind(1.d0), n = 1000
real(kind=dp), parameter :: pi = 3.14159265359d0, dt = 1.d-4, omega = 50.d0*2.d0*pi, ta = 0.040d0
real(kind=dp) t1(1:n), ac(1:n), dc(1:n), inst(1:n), xmin_data, xmax_data, ymin_data, ymax_data, xstep, ystep
real(kind=dp) x_min_now, x_max_now, y_min_now, y_max_now
contains
  integer function generate_data()
  integer i
  real(kind=dp) ran
  ran=random@()
    do i = 1, n, 1
      if (i .gt. 1) then
        t1(i) = t1(i-1) + dt
      else
        t1(i) = 0.d0
      end if
      ac(i) = ran*sqrt(2.d0)*cos(omega*t1(i)-pi)  ;  dc(i) = -ac(1)*exp(-t1(i)/ta) ; inst(i)=ac(i)+dc(i)
    end do
    generate_data = 1
  end function generate_data
  integer function plot()
  include<windows.ins>
  integer, save :: iw
    xmin_data = minval(t1)  ; xmax_data = maxval(t1)
    ymin_data = min(minval(ac), minval(dc), minval(inst)) ; ymax_data = max(maxval(ac), maxval(dc), maxval(inst))
    xstep = (xmax_data - xmin_data)/10.d0 ; ystep = (ymax_data - ymin_data)/10.d0
    x_min_now = xmin_data ; x_max_now = xmax_data ; y_min_now = ymin_data ; y_max_now = ymax_data
    call winop@('%pl[native,x_array,gridlines,n_graphs=3,width=2,frame,etched,colour=blue,colour=red,colour=black]')
    iw = winio@('%pl[full_mouse_input]&',700,600,n,t1,ac,dc,inst)
    iw = winio@('%ob[scored]&')
    iw = winio@('%2nl%cn%^tt[Zoom in]&',              zoom_in_cb)
    iw = winio@('%2nl%cn%^tt[Zoom out]&',             zoom_out_cb)
    iw = winio@('%2nl%cn%^tt[Full extents]%2nl&',     zoom_out_full_cb)
    iw = winio@('%2nl%cn%^tt[Pan pos X]&',            pan_positive_x_cb)
    iw = winio@('%2nl%cn%^tt[Pan neg X]&',            pan_negative_x_cb)
    iw = winio@('%2nl%cn%^tt[Pan pos Y]&',            pan_positive_y_cb)
    iw = winio@('%2nl%cn%^tt[Pan neg Y]&',            pan_negative_y_cb)
    iw = winio@('%2nl%cn%^tt[Simpleplot Redraw]&',    spr_cb)
    iw = winio@('%2nl%cn%^tt[New data]&',             new_data_cb)
    iw = winio@('%cb%ff%2nl%cn%tt[Close]&')
    iw = winio@(' ') ; plot = 1
  end function plot
  integer function spr_cb()
  include<windows.ins>
    call simpleplot_redraw@()
    spr_cb = 1
  end function spr_cb
  integer function new_data_cb()
  include<windows.ins>
  integer i
    i = generate_data()
    call simpleplot_redraw@()
    new_data_cb = 1
  end function new_data_cb
  integer function update_pl_limits()
  include<windows.ins>
  integer k
    k = CHANGE_PLOT_DBL@(0, 'x_min', 0, x_min_now) ; k = CHANGE_PLOT_DBL@(0, 'x_max', 0, x_max_now)
    k = CHANGE_PLOT_DBL@(0, 'y_min', 0, y_min_now) ; k = CHANGE_PLOT_DBL@(0, 'y_max', 0, y_max_now)
    call simpleplot_redraw@()           
    update_pl_limits = 1
  end function update_pl_limits
  subroutine swap_real_dp(r1,r2)
  real(kind=dp), intent(inout) :: r1, r2
  real(kind=dp) temp
    temp = r2 ; r2 = r1 ; r1 = temp
  end subroutine swap_real_dp
Back to top
View user's profile Send private message Visit poster's website
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Sat Jun 20, 2020 10:58 pm    Post subject: Reply with quote

Code:
  integer function zoom_out_cb()
  include<windows.ins>
  integer i
    x_min_now = x_min_now - xstep ; x_max_now = x_max_now + xstep ; y_min_now = y_min_now - ystep ; y_max_now = y_max_now + ystep
    i = update_pl_limits() ; zoom_out_cb = 1
  end function zoom_out_cb
  integer function zoom_in_cb()
  real(kind=dp) x_min_now_save, x_max_now_save, y_min_now_save, y_max_now_save
  integer i
  integer, save :: iw
    x_min_now_save = x_min_now ; x_max_now_save = x_max_now  ; y_min_now_save = y_min_now ; y_max_now_save = y_max_now
    x_min_now = x_min_now + xstep ; x_max_now = x_max_now - xstep ; y_min_now = y_min_now + ystep ; y_max_now = y_max_now - ystep
    if ( ( x_max_now - x_min_now .gt. xstep ) .and. ( y_max_now - y_min_now .gt. xstep ) ) then
      i = update_pl_limits()
    else
      x_min_now = x_min_now_save ; x_max_now = x_max_now_save ; y_min_now = y_min_now_save ; y_max_now = y_max_now_save
      iw = winio@('%ws%2nl%cn%tt[Continue]','Max zoom level with this control.')
    end if
   zoom_in_cb = 1
  end function zoom_in_cb
  integer function zoom_out_full_cb()
  integer i
!    x_min_now = xmin_data ; y_min_now = ymin_data ; x_max_now = xmax_data ; y_max_now = ymax_data
!   Copied from function plot() - since the extent of the data may have changed following a call to new_data
    xmin_data = minval(t1)  ; xmax_data = maxval(t1)
    ymin_data = min(minval(ac), minval(dc), minval(inst)) ; ymax_data = max(maxval(ac), maxval(dc), maxval(inst))
    xstep = (xmax_data - xmin_data)/10.d0 ; ystep = (ymax_data - ymin_data)/10.d0
    x_min_now = xmin_data ; x_max_now = xmax_data ; y_min_now = ymin_data ; y_max_now = ymax_data
    i = update_pl_limits()
    zoom_out_full_cb = 1
  end function zoom_out_full_cb
  integer function pan_positive_x_cb()
  integer i
    x_min_now = x_min_now + xstep ; x_max_now = x_max_now + xstep ; i = update_pl_limits() ; pan_positive_x_cb = 1
  end function pan_positive_x_cb
  integer function pan_negative_x_cb()
  integer i
    x_min_now = x_min_now - xstep ; x_max_now = x_max_now - xstep ; i = update_pl_limits() ; pan_negative_x_cb = 1
  end function pan_negative_x_cb
  integer function pan_positive_y_cb()
  integer i
    y_min_now = y_min_now + ystep ; y_max_now = y_max_now + ystep ; i = update_pl_limits() ; pan_positive_y_cb = 1
  end function pan_positive_y_cb
  integer function pan_negative_y_cb()
  integer i
    y_min_now = y_min_now - ystep ; y_max_now = y_max_now - ystep ; i = update_pl_limits() ; pan_negative_y_cb = 1
  end function pan_negative_y_cb
end module example
program main
use example
implicit none
integer i
i = generate_data() ; i = plot()
end program main
Back to top
View user's profile Send private message Visit poster's website
Martin_K



Joined: 09 Apr 2020
Posts: 227

PostPosted: Sun Jun 21, 2020 11:22 pm    Post subject: Reply with quote

Ken,

profound thanks for your help! Today, I had another family program so I was
not able to seat in front of my PC. I will do it within next week.

BUT, I already did what you suggest practically immediately after your advise (your post of Friday, June 19, 3.46pm)!

I was struggling with this change a while and my best result was that I achieved that the axes captions were always present (even after zooming in/out),
BUT the problem with automatic zoom to extents, when I moved with mouse cursor over graphs, remained unsolved with these changes! It means, as soon as I move the cursor over the graphs after some zooming in/out, the program automatically re-draws whole graphs to their extents.

I have to mention that I created a FUNCTION called within the block IF (cb_reason.eq. 'PLOT_ADJUST') THEN ... END IF, which contained everything, NOT SUBROUTINE! I suppose it should make no difference.

It looked as follows:

Code:

!integer function new_dll_cb()

!        CALL SELECT_GRAPHICS_OBJECT@(handle_pl)
!      call simpleplot_redraw@()
       
!      CALL select_font@('arial')
!        CALL bold_font@(1)
!!        CALL size_in_pixels@(15,15)
!        CALL size_in_points@(15,15)
!        CALL draw_characters@('Y_S-JTSK [m]',600,630,RGB@(255,0,255))
!        CALL rotate_font@(90.0d0)
!        CALL draw_characters@('X_S-JTSK [m]',90,400,RGB@(255,0,255))
!        CALL rotate_font@(0.0d0)
!   i = COPY_GRAPHICS_REGION@(handle_internal_gr, 1, 1, gw, gh, handle_pl, 1, 1, gw, gh, 13369376)

!new_data_cb = 2
!end function new_dll_cb
....
....
IF (cb_reason .eq. 'PLOT_ADJUST') THEN

i = new_dll_cb()

END IF




In next days I will create a subroutine (instead of function), if it should help to solve my problem. I will give a feedback as soon as I get something new.
At the moment I am quite sceptic, since there are some additional issues (the switching on/off of graphs does not work correctly). Since I am already under time
pressure to present the results of the whole graphics in a seminar, probably I will downgrade the DLL´s back to the previous ones,
where everything worked problem free and later, after seminar, I will try to adapt whole program to the latest DLLs, since now - the %PL command offers
very exciting features and flexibility (it would be for us as surveyors worthful, when it would be added to the %PL still the option SCALE)!.

However, my program has about 1300 lines of code in 5 different subroutines/modules, so it will not be a easy work.

Martin
Back to top
View user's profile Send private message
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Mon Jun 22, 2020 4:05 am    Post subject: Reply with quote

Paul,
Tried this new feature and my immediate wish was to set parameters in the file. If user often doing changes (adjusting minimum and maximum x and y, changing step etc) he will be forced to recompile the code every time he adjusts the plot for new variants. There exist tasks where you set the plot just ones for all future cases but in vast other life situations you need permanently change something in the plot.

Parameters are automatically saved in the filename which user provides for this specific plot, and they will be automatically loaded from same file when user next time opens this specific plot. No further intervention is needed, all done in background. This is how all my plots are set in all programs, no recompilation needed. There was no single plot ever which I set ones and never changed something in it again! Besides it is easy quickly clone old plot to new plot using existing plot settings if needed

May be there exist situations where current way of save setting could be the only practical method but I can not quickly imagine one. I understand that this was just the demo, and your route for the final product lie in different way
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Mon Jun 22, 2020 8:01 am    Post subject: Reply with quote

Dan

At the moment I don't understand what you are asking for.

Do you want ClearWin+ to offer to save the data to a file and prompt for a file name?

As it is, your program can save the data to a file and read it back on the next run. You will have to do the reading back anyway even if ClearWin+ saves to a file for you.
Back to top
View user's profile Send private message AIM Address
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Mon Jun 22, 2020 10:16 am    Post subject: Reply with quote

The mechanism within ClearWin+ that is used to block re-entry to a %pl callback from a call to simpleplot_redraw@ has been modified. With this change, calling simpleplot_redraw@ will lead to a call to the callback but a call to simpleplot_redraw@ from the %pl callback will be blocked.

New DLLs that incorporate this change can be downloaded via the link given here http://forums.silverfrost.com/viewtopic.php?t=4245.
Back to top
View user's profile Send private message AIM Address
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Mon Jun 22, 2020 12:01 pm    Post subject: Reply with quote

Martin,

your old code may well work with today's DLLs - which implement the change that was made but in a different way. I don't have time to download and test myself until this evening.

Ken
Back to top
View user's profile Send private message Visit poster's website
DanRRight



Joined: 10 Mar 2008
Posts: 2813
Location: South Pole, Antarctica

PostPosted: Mon Jun 22, 2020 1:17 pm    Post subject: Reply with quote

Paul
I meant to offer an option that settings data saved to the harddrive automatically at the exit of settings process. In this case next time you run this program it starts not with basic plot like it does for first time but already using created settings. For that additional filename has to be provided like

Call Winop@('AutoSetfile=PLplotMain01.set')

and that's basically it

Of course user can save settings by himself and read them next time program runs but that is an additional programming by the user. With above mentioned addition the user will be able to use both options for saving settings to harddrive if he wants plus use the existing saving to the clipboard with recompilation. The automatic saving settings to the disk with similarly automatic reading next time program runs the plot will be the most used I predict
Back to top
View user's profile Send private message
John-Silver



Joined: 30 Jul 2013
Posts: 1520
Location: Aerospace Valley

PostPosted: Mon Jun 22, 2020 2:29 pm    Post subject: Reply with quote

Paul said:
Quote:
As it is, your program can save the data to a file and read it back on the next run


which I assume means the user has to program the write / read of the 'file' containing the variable 'PARAMS' himself ?

Can't it be incorporated into the GUI as a button (not just the option on exit when one is prompted if one wants to save either to the clipboard or to the buffer) ?

What I'm interested in is to know the names of the complete list of parameters in the variable 'PARAMS' in their order ( see 9m23 of the video), so one can edit by hand and have a set of 'PARAMS' readily available for various different plots.
_________________
''Computers (HAL and MARVIN excepted) are incredibly rigid. They question nothing. Especially input data.Human beings are incredibly trusting of computers and don't check input data. Together cocking up even the simplest calculation ... Smile "


Last edited by John-Silver on Mon Jun 22, 2020 9:39 pm; edited 1 time in total
Back to top
View user's profile Send private message
PaulLaidler
Site Admin


Joined: 21 Feb 2005
Posts: 7916
Location: Salford, UK

PostPosted: Mon Jun 22, 2020 3:27 pm    Post subject: Reply with quote

Dan

I will see what can be done.

John

The order is coded using the following list but you will need to remove some items particularly those like line colour that vary from one line to another. Line attributes are added one line at a time at the end of the first two lists each of which is terminated by a semi-colons.


Code:
enum
{
  pl_title_ix,
  pl_title_iy,
  pl_xcap_ix,
  pl_xcap_iy,
  pl_ycap_ix,
  pl_ycap_iy,
  pl_tick_value_ix,
  pl_tick_value_iy,
  pl_xmin_supplied,
  pl_ymin_supplied,
  pl_xmax_supplied,
  pl_ymax_supplied,
  pl_x_sigfigs,
  pl_y_sigfigs,
  pl_width,
  pl_depth,
  pl_link,
  pl_pen_style,
  pl_line_width,
  pl_symbol,
  pl_symbol_size,
  pl_axes_pen,
  pl_frame_pen,
  pl_tick_len,
  pl_gridlines,
  pl_frame,
  pl_framed,
  pl_etched,
  pl_external_ticks,
  pl_fixed_aspect,
  pl_title_height,
  pl_caption_height,
  pl_tick_value_height,
  pl_back_colour,
  pl_font_colour,
  pl_margin_left,
  pl_margin_top,
  pl_margin_right,
  pl_margin_bottom,
  pl_smoothing,
  pl_idata_end
};

enum
{
  pl_xmin,
  pl_ymin,
  pl_xmax,
  pl_ymax,
  pl_ddx,
  pl_ddy,
  pl_fdata_end
};
Back to top
View user's profile Send private message AIM Address
Kenneth_Smith



Joined: 18 May 2012
Posts: 697
Location: Hamilton, Lanarkshire, Scotland.

PostPosted: Mon Jun 22, 2020 4:45 pm    Post subject: Reply with quote

Paul,

Which .mod and .inc files go alongside the new DLLs?

I'm a bit reticent to make any further changes now.

Currently, I have the new .mod and .inc files on my machine, i.e. those from the link from your post above on Fri Jun 19, 2020 8:43 am

Ken
Back to top
View user's profile Send private message Visit poster's website
Martin_K



Joined: 09 Apr 2020
Posts: 227

PostPosted: Mon Jun 22, 2020 5:09 pm    Post subject: Reply with quote

There is probably something missing with the new DLLs v48 (.mod file?), I have a problem when creating executable (TARGET DOES NOT EXIST) with FTN v8.63 and DLLs v48,
so I had to copy back the v47 DLLs. I copied the FTN v8.63 along with DLLs v48, it does not work.

As soon as I copied back the DLLs either v47 or v46, it works also with FTN v8.63.

Martin
Back to top
View user's profile Send private message
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+ All times are GMT + 1 Hour
Goto page Previous  1, 2, 3, 4, 5, 6  Next
Page 3 of 6

 
Jump to:  
You cannot post new topics in this forum
You cannot reply to topics in this forum
You cannot edit your posts in this forum
You cannot delete your posts in this forum
You cannot vote in polls in this forum


Powered by phpBB © 2001, 2005 phpBB Group