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 

Hold graph to plot many data sets

 
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+
View previous topic :: View next topic  
Author Message
Natetran77



Joined: 07 Mar 2012
Posts: 5
Location: California

PostPosted: Wed Mar 07, 2012 12:15 pm    Post subject: Hold graph to plot many data sets Reply with quote

I'm having trouble plotting my data points. Below is the Subroutine I use to plot coastal lines for a world map. The default %pl connects every data point but I don't want a line connecting each Continent. Can anyone tell me how to keep the plot window open and hold it so I can add 1 Continent at a time?

Code:
        SUBROUTINE SIMPLE(X,Y)                                                         !
c--SimplePlot.for                                                                      !
        WINAPP                                                                         !
        INTEGER N,winio@,i                                                             !
        PARAMETER(N=5116)                                                              !
        DOUBLE PRECISION x(N),y(N)                                                     !
c--Create the data to be plotted.                                                      !
C        CCR=1                                                                          !
C        ENDPLOT=0                                                                      !
9911    DO i=1,N                                                                       !
C        CCR=2                                                                          !
          READ(4,5555) x(i),y(i)                                                       !
5555    FORMAT(9X,I4,8X,I4)                                                            !
C          IF(x(i).EQ.88) GO TO 9119                                                    !
C          IF(x(i).EQ.22) ENDPLOT=1
C          IF(x(i).EQ.22) GO TO 9119                                                     !                                                                               !
        ENDDO                                                                          !
9119    CONTINUE                                                                       !
c--Plot the data.                                                                      !
C        write(6,*) CCR                                                                 !
C        IF(CCR.EQ.1) GO TO 3310                                                        !
C        IF(CCR.EQ.2) GO TO 3311                                                        !           
3310    i=winio@('%ca[SIMPLEPLOT]%bg[white]&')                                         !
                                                                                       !
3311    i=winio@('%pl[x_array]&',950,650,N,x,y)                                        !
                                                                                       !
C        IF(ENDPLOT.EQ.0) GO TO 9911                                                    !
        i=winio@('%ff%nl%cn%tt[OK]')                                                   !
        RETURN                                                                         !
        END


[img]https://docs.google.com/document/d/1c-KQif-3xD_Wi9Rx6UskoHNpIDU_7JglVwduD1NAMbM/edit[/img]
_________________
N8T
Back to top
View user's profile Send private message Send e-mail
Natetran77



Joined: 07 Mar 2012
Posts: 5
Location: California

PostPosted: Fri Mar 09, 2012 1:03 am    Post subject: Latest Attempt Reply with quote

This is my latest attempt at rewriting my subroutine. Perhaps it would be easier for everyone if I just posted both my datafile and subroutine as a program so others can attempt to run it and see what is actually plotting, yes?

Here is my data file: [url=https://docs.google.com/open?id=0Bzy5FZxLELbaVTNOUWZydzFSZS14NHV5aVlJOHBHdw[/url]

Here is version 1 where it collects all datapoints then plots:

Code:
        Program SIMPLE1
C                                                                                      C
C......................................Program1........................................C
                                                                        !
c--SimplePlot                                                           !
        WINAPP                                                          !
        INTEGER N,winio@,i                                              !
        PARAMETER(N=4890)                                               !
        DOUBLE PRECISION x(N),y(N)                                      !
c--Create the data to be plotted.                                       !
                                                                        !
        OPEN(UNIT=4, FILE='PRINTER(4).TXT', STATUS='OLD')               !                                                           !
9911    DO i=1,N                                                        !
          READ(4,*) x(i),y(i)                                           !
5555    FORMAT(9X,I4,8X,I4)                                             !                                                                            !
        ENDDO                                                           !                                                        !
                                                                        !
c--Plot the data.                                                       !
                                                                        !
        i=winio@('%ca[SIMPLEPLOT]%bg[white]&')                          !                                                                                     !
        i=winio@('%pl[x_array]&',970,621,N,x,y)                         ! 
        i=winio@('%ff%nl%cn%tt[OK (NOT)]')                                 !                                                 !
        END                                                             !
                                                                        !
C......................................................................................C
C                                                                                      C


And here, I altered to try and and plots of each dataset one on top of the next but if you run this you'll see what happens!

[code:1:9791b8e2dd]C C
C......................................PROGRAM2........................................C
!
PROGRAM SIMPLE2 !
c--SimplePlot.for !
WINAPP !
INTEGER N,winio@,i !
PARAMETER(N=4867) !
DOUBLE PRECISION x(N),y(N) !
!
c--Create the data to be plotted. !
!
OPEN(UNIT=4, FILE='PRINTER(4).TXT', STATUS='OLD') !
ENDP
_________________
N8T
Back to top
View user's profile Send private message Send e-mail
Natetran77



Joined: 07 Mar 2012
Posts: 5
Location: California

PostPosted: Fri Mar 09, 2012 1:06 am    Post subject: Reply with quote

The second code again:

Code:
C                                                                                      C
C......................................PROGRAM2........................................C
                                                                        !
        PROGRAM SIMPLE2                                                 !
c--SimplePlot.for                                                       !
        WINAPP                                                          !
        INTEGER N,winio@,i                                              !
        PARAMETER(N=4867)                                               !
        DOUBLE PRECISION x(N),y(N)                                      !
                                                                        !
c--Create the data to be plotted.                                       !
                                                                        !
        OPEN(UNIT=4, FILE='PRINTER(4).TXT', STATUS='OLD')               !
        ENDPLOT=0                                                       !
        j=0                                                             !
        GO TO 9911                                                      !
3333    CONTINUE                                                        !
        j=j+1                                                           !
9911    DO i=1,N                                                        !                                                !
          READ(4,*) x(i),y(i)                                           !
5555    FORMAT(9X,I4,8X,I4)                                             !
          IF(x(i).EQ.88) GO TO 9119                                     !
          IF(x(i).EQ.22) ENDPLOT=1                                      !
          IF(x(i).EQ.22) GO TO 9119                                     !                                                                               !
        ENDDO                                                           !
9119    CONTINUE                                                        !
                                                                        !
c--Plot the data.                                                       !
                                                                        !
        IF (i.EQ.1) GO TO 9911                                          !
        x(i)= x(i-1) !IF(x(i).EQ.88)                                    !
        y(i)= y(i-1) !IF(y(i).EQ.88)                                    !
        IF (j.GE.1) GO TO 3311                                          !
        i=winio@('%ca[SIMPLEPLOT]%bg[white]&')                          !                                                                                     !
3311    i=winio@('%pl[x_array]&',925,630,N,x,y)                         ! 
        i=winio@('%ff%nl%cn%tt[NEXT!]')                                 !
C        WRITE(6,*) 'TYPE 1 TO CONTINUE :'                              !
C        READ(5,*) R                                                    !
C        IF(R.NE.1) GO TO 2222                                          !
        IF(ENDPLOT.EQ.0) GO TO 3333                                     !     
2222    CONTINUE                                                        !                                                          !
        END                                                             !
                                                                        !
C......................................................................................C
C                                                                                      C

_________________
N8T
Back to top
View user's profile Send private message Send e-mail
PaulLaidler
Site Admin


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

PostPosted: Fri Mar 09, 2012 7:56 am    Post subject: Reply with quote

I suspect that you cannot do what you want via %pl or, at least the solution will be non-standard (you might be able to access the simpleplot dll directly with the aid of the simpleplot manuals).

More likely you will need to use a different approach based on %gr or maybe even %og.

This is just an opinion. I don't have the time to look into the details for you.
Back to top
View user's profile Send private message AIM Address
Natetran77



Joined: 07 Mar 2012
Posts: 5
Location: California

PostPosted: Fri Mar 16, 2012 2:07 am    Post subject: %gr may work but I could use an example code Reply with quote

It looks like I could possibly use %gr inside my loop that grabs the x/y coordinates from my text file called PRINTER(4).TXT. Can anyone help me make a code that looks like: ???

x(1) = 0
y(1) = 0
DO i=2,3
read(4,*) x(i), y(i)
i=winio@('%ww%gr[white,rgb_colours]&',900,600)
i=winio@('bt[OK]%lw',ctrl)
CALL draw_line_between@(x(i-1),y(i-1),x(i),y(i),RGB@(255,0,0))
END DO

If I can control which lines are plotted then my problem is solved. Does anyone have an example code like the one above they can share? If so, can you keep plotting new lines on the existing plot of old lines? Any examples will help me a lot! Thanks Rolling Eyes
_________________
N8T
Back to top
View user's profile Send private message Send e-mail
JohnCampbell



Joined: 16 Feb 2006
Posts: 2554
Location: Sydney

PostPosted: Fri Mar 16, 2012 4:32 am    Post subject: Reply with quote

You have been mixing integer and real values.
I'd also recommend changing file unit 4 to 14.
Also a format statement with error testing for the reads would help. I've assumed 2 columns of 10 characters. Comma delimeter is also supported.
Hopefully the following changes may give you some ideas of things to consider:
Code:
include <clearwin.ins>
!
   integer*4, parameter :: n = 6000
   integer*4 ix(n), iy(n), ni, i, ctrl, iostat
   real*8    x(n), y(n), xmin, xmax, ymin, ymax, factor
!
!  create window
  i = winio@ ('%ww&')
  i = winio@ ('%gr[white,rgb_colours]&',900,600)
  i = winio@ ('bt[OK]&')
  i = winio@ ('%lw',ctrl)
!
!  read the values
  xmin = 0
  xmax = 0
  ymin = 0
  ymax = 0
  x(1) = 0
  y(1) = 0
  do i = 2,n
    read(14,fmt='(bn,2f10.0)',iostat=iostat) x(i), y(i)
    if (iostat < 0) exit
    if (iostat > 0) write (*,*) 'Error reading line',i,' of data'
    if (x(i) < 0) exit
    if (xmin > x(i)) xmin = x(i)
    if (xmax < x(i)) xmax = x(i)
    if (ymin > y(i)) ymin = y(i)
    if (ymax < y(i)) ymax = y(i)
  end do
  ni = i-1
!
!  scale the values
  factor = min ( 800. / (xmax-xmin), 500. / (ymax-ymin) )
  do i = 1,ni
    ix(i) = (x(i)-xmin) * factor + 50
    iy(i) = (y(i)-ymin) * factor + 50
  end do
!
!  plot values X,y where X must be in the range 0:900 and y 0:600
  DO i=2,ni
    CALL draw_line_between@ (ix(i-1),iy(i-1), ix(i),iy(i), RGB@(255,0,0))
  END DO
!
end
Back to top
View user's profile Send private message
BillBardsley



Joined: 19 Mar 2012
Posts: 3

PostPosted: Tue Mar 20, 2012 11:32 am    Post subject: Re: Hold graph to plot many data sets Reply with quote

[quote="Natetran77"]I'm having trouble plotting my data points. Below is the Subroutine I use to plot coastal lines for a world map. The default %pl connects every data point but I don't want a line connecting each Continent. Can anyone tell me how to keep the plot window open and hold it so I can add 1 Continent at a time?

Use the technique demonstrated in simdem46 which has many afvantages.
1) Areas can be outlined or filled with colour
2) Additional structures can be added (see the K-means example plot)
3) High resolution eps files can be archived
4) You can compile the main program in 64-bit and still use the code

Bill
Back to top
View user's profile Send private message
Natetran77



Joined: 07 Mar 2012
Posts: 5
Location: California

PostPosted: Fri Mar 23, 2012 12:39 am    Post subject: Reply with quote

Okay! I've made much progress since my last post. I implemented JohnCampbell's example code into my main program and it's running great Very Happy These are the links to the files needed to run if anyone wants to try it out: (again, I'm running XP SP2 32 bit... so I don't need .txt extentions)

NUPLOTz.FOR (The Main Program)
https://docs.google.com/open?id=0Bzy5FZxLELbaZHk2V1Q1X29SbVc3NGJTa0x1Y3RlZw

TAH (The first file my program asks for)
https://docs.google.com/open?id=0Bzy5FZxLELbaUnlfeEJpTlRUeTI5OTh5dHZBYk9Hdw

MAP1 (The second file asked for containing map coordinates)
https://docs.google.com/open?id=0Bzy5FZxLELbaY2FkLWg5MVpTaXE5aGhNMW9oWEdNUQ

Next, I'd like to be able to interact with the map, adding lines using the mouse pointer, plotting points and maybe even adding a [PRINT] button if possible. I've tried using the windows print commands but I get an Access error. Thanks John and everyone else that has commented.
_________________
N8T
Back to top
View user's profile Send private message Send e-mail
Display posts from previous:   
Post new topic   Reply to topic    forums.silverfrost.com Forum Index -> ClearWin+ All times are GMT + 1 Hour
Page 1 of 1

 
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