Here it is some more FORTRAN sample code :

 

Plot

      program plotit
c
c    Program to provide plots of Sin(x)
c    Ascii Character plots go to terminal and file 'pplot.out'
c
c    John Mahaffy 1/25/95
c
      implicit none
      character line*72
      real x
      integer ip,i
      character xlabel*32,ylabel*32,title*32
      real fx
c
c   line    –   Character string loaded with a line of output
c   ip      –   Position in line for a function value
c   xlabel  –   Contains a label for the x-axis
c   ylabel  –   Contains a label for the y-axis
c   title   –   Contains a title for the plot
c
      open (11,file='pplot.out')
c
c   Label values of the y axis
c
      line=' '
      line(14:15)='-1'
      line(65:65)='1'
      write(*,*) line
      write(11,*) line
      line=' '
      line(11:13)='0.0'
c
c   Draw the y axis
c
      line(15:40)='+—-+—-+—-+—-+—-+'
      line(41:65)=line(16:40)
c
c   Plot the value at x=0
c     <a name=2><font color=FF0000>
      ip= nint(25*sin(0.0))+40
c     </font>
      line(ip:ip)='*'
      write(*,*) line
      write(11,*) line
      line=' '
c
c    Loop through and plot points for other x values
c
      do 50 i=1,60
         x=.1*i
c     <a name=1><font color=FF0000>
         ip=nint(25*sin(x))+40
c     </font>
c     <a name=3><font color=98404f>
         if(mod(i,10).eq.0) then
c     </font>
            write(line(10:13),'(f4.1)') x
            line(40:40)='+'
         else
            line(10:13)=' '
            line(40:40)='|'
         endif
         line(ip:ip)='*'
         write(*,*) line
         write(11,*) line
 50      line(ip:ip)=' '
      close (11)
c
c   Drive a separate true graphics program (gnuplot)
c
c   First set up the command file for gnuplot
c
      xlabel='''x'''
      ylabel='''y'''
      title='''sin(x)'''
      open (12,file='gnuxy')
c
c   UnComment the next line if you are on an NCSA/BYU Telnet Session
c
c     write(12,*) 'set terminal tek40xx'
c
      write(12,*) 'set data style lines'
      line='set xlabel '//xlabel
      write(12,*)line
      line='set ylabel '//ylabel
      write(12,*)line
      line='set title '//title
      write(12,*)line
      write(12,*)'set nokey'
      write(12,*)'set xrange [0:6]'
      write(12,*) 'plot ''dataxy'' using 1:2'
      write (12,*) 'pause -1'
      close(12)
c
c   Generate x-y pairs for the graph
c
      open (12,file='dataxy')
      do 100 i=0,60
         x=.1*i
         fx=sin(x)
         write(12,*) x,fx
  100 continue
      close(12)
c
      print *, ' Hit the Return (Enter) key to continue'
c
c   Tell the system to run the program gnuplot
c   This call works on either IBM RS6000 or Sun, but is not part of
c   the Fortran standard.
c   Comment out the line if you aren't at a terminal with graphics
c
      call system ('gnuplot gnuxy')
c<a name="stop"><font color="FF0000">
      stop
c</font></a>
      end
c</pre>
c</body>
c</html>

 

 

Ssort

c<html>
c<head><title>sort1.f</title></head>
c<body>
c<pre>      
    SUBROUTINE SSORT (X, IY, N, KFLAG)
      IMPLICIT NONE
c
c    Example of a Selection Sort   Using a Fortran 90 Intrinsic Function
c
C***BEGIN PROLOGUE  SSORT
C***PURPOSE  Sort an array and make the same interchanges in
C            an auxiliary array.  The array is sorted in
C            decreasing order.
C***TYPE      SINGLE PRECISION
C***KEYWORDS  SORT, SORTING
C
C   Description of Parameters
C      X – array of values to be sorted   (usually abscissas)
C      IY – array to be carried with X (all swaps of X elements are
C          matched in IY .  After the sort IY(J) contains the original
C          postition of the value X(J) in the unsorted X array.
C      N – number of values in array X to be sorted
C      KFLAG – Not used in this implementation
C
C***REVISION HISTORY  (YYMMDD)
C   950310  DATE WRITTEN
C   John Mahaffy

C***END PROLOGUE  SSORT
C     .. Scalar Arguments ..
      INTEGER KFLAG, N
C     .. Array Arguments ..  —–NOTE the 2 new ways of declaring array size
      REAL X(1:N)
      INTEGER IY(N)
C     .. Local Scalars ..
      REAL TEMP
      INTEGER I, ISWAP(1), ITEMP, ISWAP1
C     .. External Subroutines ..
C     None
C     .. Intrinsic Functions ..
      INTRINSIC MAXLOC
c
c
c    MAXLOC is a FORTRAN 90 function that returns the index value for the
c    maximum element in the array
C***FIRST EXECUTABLE STATEMENT  SSORT
C
      DO 200 I=1,N1
c<a name=1><font color=FF0000>
         ISWAP=MAXLOC(X(I:N))

c</font>
         ISWAP1=ISWAP(1)+I1
         IF(ISWAP1.NE.I) THEN
           TEMP=X(I)
            X(I)=X(ISWAP1)
            X(ISWAP1)=TEMP
            ITEMP=IY(I)
            IY(I)=IY(ISWAP1)
            IY(ISWAP1)=ITEMP
         ENDIF
  200 CONTINUE
      RETURN
      END
c</pre>
c</body>
c</html>
 

      SUBROUTINE SSORT (X, IY, N, KFLAG)
      IMPLICIT NONE
c
c    Example of a Bubble Sort
c
C***BEGIN PROLOGUE  SSORT
C***PURPOSE  Sort an array and make the same interchanges in
C            an auxiliary array.  The array is sorted in
C            decreasing order.
C***TYPE      SINGLE PRECISION
C***KEYWORDS  SORT, SORTING
C
C   Description of Parameters
C      X – array of values to be sorted   (usually abscissas)
C      IY – array to be carried with X (all swaps of X elements are
C          matched in IY .  After the sort IY(J) contains the original
C          postition of the value X(J) in the unsorted X array.
C      N – number of values in array X to be sorted
C      KFLAG – Not used in this implementation
C
C***REVISION HISTORY  (YYMMDD)
C   950310  DATE WRITTEN
C   John Mahaffy
C***END PROLOGUE  SSORT
C     .. Scalar Arguments ..
      INTEGER KFLAG, N
C     .. Array Arguments ..
      REAL X(*)
      INTEGER IY(*)
C     .. Local Scalars ..
      REAL TEMP
      INTEGER I, J, JMAX, ITEMP
C     .. External Subroutines ..
C     None
C     .. Intrinsic Functions ..
C     None
C
C***FIRST EXECUTABLE STATEMENT  SSORT
C
      JMAX=N1
      DO 200 I=1,N1
         TEMP=1.E38
         DO 100 J=1,JMAX
            IF(X(J).GT.X(J+1)) GO TO 100
              TEMP=X(J)
              X(J)=X(J+1)
              X(J+1)=TEMP
              ITEMP=IY(J)
              IY(J)=IY(J+1)
              IY(J+1)=ITEMP
  100    CONTINUE
         IF(TEMP.EQ.1.E38) GO TO 300
         JMAX=JMAX1
  200 CONTINUE
  300 RETURN
      END
      SUBROUTINE SSORT (X, IY, N, KFLAG)
      IMPLICIT NONE
 

Insertion Sort

c
c    Example of an Insertion Sort
c
C***BEGIN PROLOGUE  SSORT
C***PURPOSE  Sort an array and make the same interchanges in
C            an auxiliary array.  The array is sorted in
C            decreasing order.
C***TYPE      SINGLE PRECISION
C***KEYWORDS  SORT, SORTING
C
C   Description of Parameters
C      X – array of values to be sorted   (usually abscissas)
C      IY – array to be carried with X (all swaps of X elements are
C          matched in IY .  After the sort IY(J) contains the original
C          postition of the value X(J) in the unsorted X array.
C      N – number of values in array X to be sorted
C      KFLAG – Not used in this implementation
C
C***REVISION HISTORY  (YYMMDD)
C   950310  DATE WRITTEN
C   John Mahaffy
C***END PROLOGUE  SSORT
C     .. Scalar Arguments ..
      INTEGER KFLAG, N
C     .. Array Arguments ..
      REAL X(*)
      INTEGER IY(*)
C     .. Local Scalars ..
      REAL TEMP
      INTEGER I, J, K, ITEMP
C     .. External Subroutines ..
C     None
C     .. Intrinsic Functions ..
C     None
C
C***FIRST EXECUTABLE STATEMENT  SSORT
C
      DO 100 I=2,N
         IF ( X(I).GT.X(I1) ) THEN
            DO 50 J=I2,1,-1
              IF(X(I).LT.X(J)) go to 70
  50          CONTINUE
            J=0
  70        TEMP=X(I)
            ITEMP=IY(I)
            DO 90 K=I,J+2,-1
              IY(K)=IY(K1)
  90          X(K)=X(K1)
            X(J+1)=TEMP
            IY(J+1)=ITEMP
         ENDIF
  100 CONTINUE
      RETURN
      END
 

Most of sample codes are taken from http://www.personal.psu.edu/jhm/f90/progref.html

Gg1