mat_plot Subroutine

public subroutine mat_plot(lplot, x, y, n, p, k)

Arguments

Type IntentOptional Attributes Name
integer :: lplot
doubleprecision :: x(n)
doubleprecision :: y(n)
integer :: n
doubleprecision :: p(*)
integer :: k

Contents

Source Code


Variables

Type Visibility Attributes Name Initial
integer, public :: ch
doubleprecision, public :: dx
doubleprecision, public :: dy
integer, public, parameter :: h = 20
integer, public :: i
integer, public :: ios
integer, public :: j
integer, public :: jmax
integer, public :: l

if (k .gt. 0) write(lplot,01) (p(i), i=1,k) 01 FORMAT(‘Extra parameters’,*(f5.1,/))

integer, public :: lets(k)
character(len=79), public :: pbuf
character(len=k), public :: string
integer, public :: tlun
integer, public, parameter :: w = 79
doubleprecision, public :: xmax
doubleprecision, public :: xmin
doubleprecision, public :: y0
doubleprecision, public :: y1
doubleprecision, public :: ymax
doubleprecision, public :: ymin

Source Code

subroutine mat_plot(lplot,x,y,n,p,k)

! ident_24="@(#) M_matrix mat_plot(3fp) Plot X vs. Y on LPLOT. If K is nonzero then P(1) ... P(K) are extra parameters"

integer           :: lplot
integer           :: n
doubleprecision   :: x(n)
doubleprecision   :: y(n)
doubleprecision   :: p(*)
integer           :: k

integer           :: lets(k)
character(len=k)  :: string
doubleprecision   :: xmin,ymin,xmax,ymax,dy,dx,y1,y0
character(len=79) :: pbuf                             ! work space for ascii plot
integer,parameter :: h=20,w=79                        ! h = height, w = width
integer           :: tlun
integer           :: ios
integer           :: ch
integer           :: i
integer           :: j
integer           :: jmax
integer           :: l

!!      if (k .gt. 0) write(lplot,01) (p(i), i=1,k)
!!   01 FORMAT('Extra parameters',*(f5.1,/))

   xmin = x(1)
   xmax = x(1)
   ymin = y(1)
   ymax = y(1)

   do i = 1, n
      xmin = dmin1(xmin,x(i))
      xmax = dmax1(xmax,x(i))
      ymin = dmin1(ymin,y(i))
      ymax = dmax1(ymax,y(i))
   enddo

   dx = xmax - xmin
   if (dx .eq. 0.0d0) dx = 1.0d0
   dy = ymax - ymin
   write(lplot,'(80x)')
   do l = 1, h
      pbuf(:)=' '  ! blank out the line
      y1 = ymin + (h-l+1)*dy/h
      y0 = ymin + (h-l)*dy/h
      jmax = 1
      do i = 1, n
         if (y(i) .gt. y1) cycle
         if (l.ne.h .and. y(i).le.y0) cycle
         j = 1 + (w-1)*(x(i) - xmin)/dx
         pbuf(j:j) = '*'
         jmax = max(jmax,j)
      enddo
      write(lplot,'(1x,a)') pbuf(1:jmax)
   enddo

   ! set up the data file
   open(newunit=tlun,file='xy.dat')
   do i=1,n
      write(tlun,*)x(i),y(i)
   enddo
   flush(tlun)

   string=' '
   lets=0
   do i=1,k
      ch=p(i)
      if ((ch.ge.0) .and. (ch.lt.G_CHARSET_SIZE)) then
         lets(i) = ch
      endif
   enddo
   call mat_buf2str(string,lets,k)

   ! call the external program xy(1) converting the parameters to a string of options
   call journal('sc','xy xy.dat ',trim(string))
   call execute_command_line('xy xy.dat '//trim(string))
   close(unit=tlun,status='delete',iostat=ios)

end subroutine mat_plot