Program create_doc Implicit None Integer I,J,K,numsub,Unitnm(0:200),Sizehd(0:200),End(0:200),start,loc,M, + locarr(50),starto,headar(50),ndum,match Character Line*100,header(100)*200,Asizeh(0:200)*3,lineout*200 C Declarations needed to get arguments from MPW command line. C Argument 0 is always create_doc and is ignored. Arguments 2 and up are the C actual files that will be searched to build the documentation. Argument C 1 is the directory containing the files. include 'Types.f' STRUCTURE /Args/ record /StringPtr/ arg(0:7) END STRUCTURE integer*4 ArgC pointer /Args/ ArgV integer*4 JARGC ! ArgC = JArgC() EXTERNAL JARGC ! # of arguments+1 integer*4 JARGV ! ArgV = JArgV() EXTERNAL JARGV ! pointer to an array of string pointers record /StringPtr/ P integer*4 p Data UnitNm/201*0/ Open(Unit=1,File='pgplot.doc',Status='Unknown',Err=2000, + carriagecontrol='Fortran') Open(Unit=2,File='pgplot.html',Status='Unknown',Err=3000, + carriagecontrol='Fortran') c 1 2 3 4 5 6 7 c2345678901234567890123456789012345678901234567890123456789012345678901234567890 Write(1,'(''PGPLOT GRAPHICS SUBROUTINE LIBRARY Version 5.0'',//, +''PGPLOT is a Fortran subroutine package for drawing graphs on a variety'',/, +"of display devices. For more details, see the manual ``PGPLOT Graphics",/, +"Subroutine Library'''' available from T. J. Pearson",/, +''(tjp@astro.caltech.edu).'',//, +''INDEX OF ROUTINES'',/)') Write(2,'("",/, +"
CALL
",/,
+"statement, but make sure that the constant or expression has the",/,
+"correct data type.",//,
+"INTEGER
arguments:",/,
+"INTEGER
or INTEGER*4
in the calling program,",/,
+"not INTEGER*2
.",/)')
Write(2,'("REAL
arguments:",/,
+"REAL
or REAL*4
in the calling program, not",/,
+"REAL*8
or DOUBLE PRECISION
.",//,
+"LOGICAL
arguments:",/,
+"LOGICAL
or LOGICAL*4
in the calling program.",//,
+"CHARACTER
arguments:",/,
+"CHARACTER
variable may be used (declared",/,
+"CHARACTER*n
for some integer n
).",//,
+"",///, +"
'')') if (Unitnm(J-1) .ne. Unitnm(J)) then Open(10,file=ArgV^.arg(1).P^//ArgV^.arg(Unitnm(J)).P^, + Status='OLD') End If 20 Continue Read(10,'(A100)',End=30) line If (line(1:2) .ne. 'C+') Go to 20 25 Read(10,'(A100)',End=30) line If (line(1:3) .ne. 'C--') Then sizehd(0) = len(trim(line)) If (line(1:1) .eq. ' ') Then Write(Asizeh(0),'(I3)') sizehd(0) Write(1,'(T1,A'//Asizeh(0)//')') line(1:sizehd(0)) Write(2,'(T1,A'//Asizeh(0)//')') line(1:sizehd(0)) Go to 25 Else Write(Asizeh(0),'(I3)') max(0,sizehd(0)-2) Write(1,'(T1,A'//Asizeh(0)//')') line(3:sizehd(0)) End If lineout = '' starto = 1 I = 3 50 Continue If (line(I:I) .eq. '<') Then lineout(starto:starto+3) = '<' I = I + 1 starto = starto + 4 Else if (line(I:I) .eq. '>') then lineout(starto:starto+3) = '>' I = I + 1 starto = starto + 4 Else if (line(I:I) .eq. '&') Then lineout(starto:starto+4) = '&' I = I + 1 starto = starto + 5 Else If (line(I:I) .eq. 'P') Then If ((I .lt. sizehd(0)) .and. (line(I+1:I+1) .eq. 'G')) Then match = 0 Do 55 K = 1, numsub If (((sizehd(0) - I+1) .ge. end(K)) + .and. (line(I+2:I-1+end(K)) .eq. header(K)(3:end(K))))Then match = Match + 1 headar(match) = K End If 55 Continue If (match .ge. 1) Then ndum = headar(1) If (match .gt. 1) Then Do 56 K = 1, Match - 1 If (end(headar(K+1)) .gt. end(ndum)) Then ndum = headar(K+1) End If 56 Continue End If lineout(starto:starto+15+2*end(ndum)) = ''// + header(ndum)(1:end(ndum))//'' starto = starto + 16 + 2*end(ndum) I = I + end(ndum) Else lineout(starto:starto) = line(I:I) I = I + 1 starto = starto + 1 End If Else lineout(starto:starto) = line(I:I) I = I + 1 starto = starto + 1 End If Else lineout(starto:starto) = line(I:I) I = I + 1 starto = starto + 1 End If If (I .le. sizehd(0)) Go to 50 C Write out line to pgplot.html. sizehd(0) = len(trim(lineout)) Write(Asizeh(0),'(I3)') sizehd(0) Write(2,'(T1,A'//Asizeh(0)//')')lineout(1:sizehd(0)) Go to 25 Else Write(2,'(T1,'''')') End If 30 Continue Write(2,'(T1,''