c EXAMPLE OF OUTPUT (looks better if you choose IBM PC line graphics): c /--------- pro Sample,a,b,c | 1 c | a=indgen(15)^2 | 2 c |/-------- if a eq b then begin | 3 c || print,'A equals B' | 4 c || c=0 | 5 c |+-------- endif else begin | 6 c || print,'A does not equal B' | 7 c || c=1 | 8 c |\-------- endif | 9 c \--------- end | 10 c Diagrams IDL, PV-WAVE, GDL, and FL begin(or case)-end constructs, functions c and procedures, places a * next to goto and return statements. c It places = next to lines with only comments. c Designed by mitch grunes, in his own time. c Program by Mitchell R Grunes. c Revision date: 6/17/2020. c If you find it useful, or find a problem, please send me e-mail. c WARNING: This was based on old versions of IDL and PV-WAVE! c ----------------------------------------------------- c This program was written in FORTRAN, for historic reasons. c This was written in Fortran 77 (with common extensions) for c portability. It should also compile under Fortran 90 and Fortran 95, c provided you tell the compiler it is in card format. c--------------------------------------------------------------------- c I hope this works for you, but bear in mind that nothing short of c a full-fledged language parser could really do the job. Perhaps c worth about what you paid for it. (-: c There are procedures to run this from a command line, and there are c versions for Fortran (card and free formats),IDL, PV-WAVE, GDL, FL, c C, C++, HTML and XML. c See http://mgrunes.com/diagram/index.html for more info. c----------------------------------------------------------------------- function LenA(a) ! Length of string, at least 1 c Program by Mitchell R Grunes. c Revision date: 11/22/2017. character*(*) a n=len(a) dowhile(n.gt.1.and.a(n:n).eq.' ') n=n-1 enddo LenA=n end c----------------------------------------------------------------------- function iRd(a,iDefault) ! Read prompted integer from stdin. ! if user enters "/", pick iDefault. ! Echo result to standard output. c Program by Mitchell R Grunes. c Revision date: 5/15/2017. character*(*) a print*,a(1:lenA(a))//':' i=iDefault read*,i print*,i iRd=i end c----------------------------------------------------------------------- character*5000 function aRd(a) ! Read prompted string from stdin. ! Echo result to standard output. ! Used for filenames. c Program by Mitchell R Grunes. c Revision date: 5/15/2017. character*(*) a character*5000 b print*,a(1:len(a))//':' b=' ' read(*,'(100(100a1))')(b(i:i),i=1,5000) print*,b(1:lenA(b)) aRd=b end c----------------------------------------------------------------------- subroutine Warn(Message,form,fout,a) ! Issue a warning c Program by Mitchell R Grunes. c Revision date: 6/17/2020. character*(*) Message character*(*) form logical fout character*5000 a if(fout)write(2,*)'***WARNING ',Message,': Line ', & form(1:lenA(form)),':' print*, '***WARNING ',Message,': Line ', & form(1:lenA(form)),':' if(fout)print*,a(1:LenA(a)) print*,char(7) end c----------------------------------------------------------------------- subroutine Errr(Message,form,fout,a) ! Issue an error c Program by Mitchell R Grunes. c Revision date: 6/17/2020. character*(*) Message character*(*) form logical fout character*5000 a if(fout)write(2,*)'***ERROR ',Message,': Line ', & form(1:lenA(form)),':' print*, '***ERROR ',Message,': Line ', & form(1:lenA(form)),':' if(fout)print*,a(1:LenA(a)) print*,char(7) end c----------------------------------------------------------------------- logical function find(a,b,icond) ! find b in a, subject to ! conditions: ! icond=sum of the following: ! 1: Prior, if exists, must ! be blank ! 2: Must be first non-blank ! 4: Prior character, if ! present, must not be ! alphanumeric. ! 8: Prior character, if ! present, must be blank ! or ) ! 16: Prior character, if ! present, must be blank ! or , ! 32: Next character not ! alphanumeric ! 64: Next character not ! alphabetic ! 128:Next character must be ! blank or ( ! 256:1st non-blank, possibly ! except for numeric ! labels C Caution: This program varies from one main program to the next. c Program by Mitchell R Grunes. c Revision date: 5/15/2017. character*(*) a,b character*1 c,cNext,c2 common icol,icol1 logical result ii=len(a) jj=len(b) result=.false. do i=1,ii-jj+1 if(a(i:i+jj-1).eq.b)then icol1=i ! icol1=column of item found icol =i+jj ! icol =column after item ! found c=' ' cNext=' ' if(icol1.gt.1)c=a(icol1-1:icol1-1) if(icol .le.ii)cNext=a(icol:icol) result=.true. if(result.and.iand(icond,1).ne.0.and.icol1.gt.1)then result=c.eq.' ' endif if(result.and.iand(icond,2).ne.0.and.icol1.gt.1)then result=a(1:icol1-1).eq.' ' endif if(result.and.iand(icond,4).ne.0) & result=(c.lt.'0'.or.c.gt.'9').and.(c.lt.'a'.or.c.gt.'z') if(result.and.iand(icond,8).ne.0)result=c.eq.' '.or.c.eq.')' if(result.and.iand(icond,16).ne.0)result= & c.eq.' '.or.c.eq.',' if(result.and.iand(icond,32).ne.0) & result=(cNext.lt.'0'.or.cNext.gt.'9').and. & (cNext.lt.'a'.or.cNext.gt.'z') if(result.and.iand(icond,64).ne.0) & result=(cNext.lt.'a'.or.cNext.gt.'z') if(result.and.iand(icond,128).ne.0) & result=cNext.eq.' '.or.cNext.eq.'(' if(result.and.iand(icond,256).ne.0.and.icol1.gt.1)then ii=1 do iii=1,icol1-1 c2=a(iii:iii) if(c2.ge.'0'.and.c2.le.'9')ii=iii+1 if(c2.ne.' '.and.(c2.lt.'0'.or.c2.gt.'9'))goto 20 enddo 20 if(ii.lt.icol1)then result=a(ii:icol1-1).eq.' ' endif endif find=result if(result)return endif enddo find=result end c----------------------------------------------------------------------- Function iRdLin(iUnit,fOut,MaxL,a,nLine,form)! Read line from input file... ! Function returns Returns non-zero ! at end of file. ! Handle form feeds, expand tabs, ! and drop non-ascii characters. ! --- Inputs -- integer iUnit ! File unit # logical fOut ! .true. if outputing to a file. integer MaxL ! Length over which should issue warning. ! --- Outputs -- character*5000 a ! The output line. character*5 form ! Output formatted line #. ! --- Input and Output --- integer nLine ! Line number -- incremented c Program by Mitchell R Grunes. c Revision date: 5/15/2017. character*5000 b a=' ' read(iUnit,'(100(100a1))',end=99)(a(i:i),i=1,5000) nLine=nLine+1 b=' ' ! Format line # write(b,'(i5)')nLine form=b if(a(1:1).eq.char(12))then if(fout)write(2,'(a1,:)')char(12) if(.not.fout)print*,'------------FORM FEED------------' a=a(2:5000) endif b=' ' ! Expand tabs to spaces, ! Drop non-ascii characters. i2Long=0 ! not yet marked too long iLong=0 ! not yet marked long j=1 ! Output Column # do i=1,LenA(a) if(a(i:i).eq.char(9))then ! char(9) is tab j=(j-1)/8*8+8+1 ! Ascii printable characters ! are between ' ' and char(128) elseif(a(i:i).ge.' '.and.a(i:i).lt.char(128))then if(j.le.5000)b(j:j)=a(i:i) j=j+1 if(a(i:i).ne.' '.and.j.ge.5000-10.and.i2Long.eq.0)then call Warn('Line too long to diagram',form,fout,a) i2Long=1 elseif(a(i:i).ne.' '.and.j.gt.MaxL.and.iLong.eq.0)then call Warn('Line over warning length',form,fout,a) iLong=1 endif endif enddo a=b iRdLin=0 return 99 iRdLin=1 end c----------------------------------------------------------------------- ! Format Output Line subroutine FormLine(b,fout,nColPre,i1,i2,i3,i4, & i1pp,i2pp,i3pp,i4pp,igoto,LCol,form,icomment,icomment2, & icomment3,iGraphics) c Program by Mitchell R Grunes. c Revision date: 11/22/2017. implicit none ! --- Inputs (some may actually be modified) -- character*5000 b ! Source code Line being output logical fout ! Outputing to file (unit 2)? integer nColPre ! # of cols used to diagram preprocessor directives; 0=none. ! 12 for diagramc; 0 for diagramf, diagramh, diagrami. integer i1 ! # of nest levels before current line integer i2 ! # of nest levels on current line integer i3 ! # of nest levels after current line integer i4 ! Non 0 if start or end of block integer i1pp,i2pp,i3pp,i4pp ! Similar to above for preprocessor integer igoto ! non 0 if there is a goto in line integer LCol ! Column in which to write line #'s; 0=none character*5 form ! Formatted line # integer icomment ! Non 0 if inside comment. integer icomment2 ! Is there anything outside comment? integer icomment3 ! Did a comment occur? ! --- Input and Output --- integer iGraphics ! Non-0 to use IBM PC graphics characters ! --- Internal --- integer iBlock ! Index into Block begin array (1=single line, 2=double) integer nColLin ! # of cols available to diagram, ! including preprocessor stuff=12. external LenA integer LenA ! Symbols which will mark block actions: character*1 BlockBegin (2) /'/','/'/ ! Start of block character*1 BlockEnd (2) /'\','\'/ ! End of block character*1 BlockElse (2) /'+','+'/ ! Else construct character*1 BlockContinue (2) /'|','|'/ ! Block continues w/o change character*1 BlockHoriz (2) /'-','-'/ ! Horizontal to start of line ! Same as above, but allows horizontal line to continue through: character*1 BlockBeginH (2) /'/','/'/ ! Start of block character*1 BlockEndH (2) /'\','\'/ ! End of block character*1 BlockElseH (2) /'+','+'/ ! Else construct character*5000 a ! formatted output line integer n,i,j,LastUse character*1 c if(iGraphics.ne.0)then iGraphics=1 BlockBegin (1)=char(218) ! (1)=normal BlockEnd (1)=char(192) BlockElse (1)=char(195) BlockContinue(1)=char(179) BlockHoriz (1)=char(196) BlockBeginH (1)=char(194) BlockEndH (1)=char(193) BlockElseH (1)=char(197) BlockBegin (2)=char(214) ! (2)=DO/FOR loops (doubled) BlockEnd (2)=char(211) ! (not yet used) BlockElse (2)=char(199) BlockContinue(2)=char(186) BlockHoriz (2)=char(196) BlockBeginH (2)=char(209) BlockEndH (2)=char(208) BlockElseH (2)=char(215) endif iBlock=1 ! Not using doubled lines for now nColLin=12 ! Output Columns Usage ! -------------- ------------------------------ ! 1 '='=Comment, '*'=jump ! 2 to 1+nColPre Diagrams preprocessor directives ! 2+nColPre to 1+nColLin Diagrams everything else; ! blank lines at start of code also used. ! 2+nColLin to 5000 The Code ! Also continued horizontal lines from ! above ! 1+nColLin+LCol:+nColLin+LCol If, blank, | and line # a=' ' if(i1.lt.0.or.i2.lt.0.or.i3.lt.0.or.i4.lt.0)then call Errr('Invalid diagramming index',form,fout,b) i1=max(i1,0) i2=max(i2,0) i3=max(i3,0) i4=max(i4,0) endif i2=max(i1,i3) ! Revise i2 i4=max(i4,iabs(i3-i1)) ! Fix if i3.gt.i1 a=' ' a(2+nColLin:5000)=b if(1+nColLin+LenA(b).gt.5000) & call Warn('Too many columns to diagram',form,fout,b) if(igoto.ne.0)a(1:1)='*' ! Place * next to jumps if(icomment.ne.0)icomment3=1 if(icomment2.ne.1.and.icomment3.ne.0.)a(1:1)='=' ! Place = next to line with only comments LastUse=2 ! Last usable diagram col - includes blank space at start of code dowhile(LastUse.lt.5000.and.a(LastUse:LastUse).eq.' ') LastUse=LastUse+1 enddo LastUse=LastUse-2 ! But leave one blank space before. if(max(i2,i3).gt.0)then ! Draw one vertical line per nest level do i=1,max(i2,i3) j=i + 1+nColPre if(j.le.LastUse) a(j:j)=BlockContinue(iBlock) enddo if(i4.ne.0)then ! Draw horizontal lines inward from above do i=j+1,LastUse a(i:i)=BlockHoriz(iBlock) enddo endif endif do i=1,i4 ! May need to replace some ! vertical lines with c= BlockElse(iBlock) ! else symbol if(i1.lt.i3)c=BlockBegin(iBlock) ! or begin symbol if(i1.gt.i3)c=BlockEnd (iBlock) ! or end symbol j=max(2+nColPre,i2+1-i+1) if(j.le.LastUse)then a(j:j)=c if(a(j+1:j+1).eq.BlockElse (iBlock)) ! Continue horizontal lines & a(j+1:j+1) = BlockElseH (iBlock) if(a(j+1:j+1).eq.BlockBegin (iBlock)) & a(j+1:j+1) = BlockBeginH(iBlock) if(a(j+1:j+1).eq.BlockEnd (iBlock)) & a(j+1:j+1) = BlockEndH (iBlock) endif enddo if(nColPre.gt.0)then ! Similar for preprocessor if(i1pp.lt.0.or.i2pp.lt.0.or.i3pp.lt.0.or.i4pp.lt.0)then call Errr('Invalid diagramming index',form,fout,b) i1pp=max(i1pp,0) i2pp=max(i2pp,0) i3pp=max(i3pp,0) i4pp=max(i4pp,0) endif i2pp=max(i1pp,i3pp) i4pp=max(i4pp,iabs(i3pp-i1pp)) LastUse=1+nColPre if(max(i2pp,i3pp).gt.0)then do i=1,max(i2pp,i3pp) j=i + 1+nColPre if(j.le.LastUse) a(j:j)=BlockContinue(iBlock) enddo if(i4pp.ne.0)then do i=j+1,LastUse a(i:i)=BlockHoriz(iBlock) enddo endif endif do i=1,i4pp c= BlockElse(iBlock) if(i1pp.lt.i3pp)c=BlockBegin(iBlock) if(i1pp.gt.i3pp)c=BlockEnd (iBlock) j=max(2+nColPre,i2pp+1-i+1) if(j.le.LastUse)then a(j:j)=c if(a(j+1:j+1).eq.BlockElse (iBlock)) & a(j+1:j+1) = BlockElseH (iBlock) if(a(j+1:j+1).eq.BlockBegin (iBlock)) & a(j+1:j+1) = BlockBeginH(iBlock) if(a(j+1:j+1).eq.BlockEnd (iBlock)) & a(j+1:j+1) = BlockEndH (iBlock) endif enddo endif if(LCol.gt.0.and.a(1+nColLin+LCol:5000).eq.' ')then ! Include line # if(form(1:1).eq.' ')form(1:1)=BlockContinue(iBlock) a(1+nColLin+LCol:5000)=form endif n=LenA(a) ! Output diagrammed line if(.not.fout)write(*,'(1x,100(100a1))')(a(i:i),i=1,n) if(fout) write(2,'(100(100a1))')(a(i:i),i=1,n) if(.not.fout)write(*,'(100(100a1))')(a(i:i),i=1,n) i1=i3 i1pp=i3pp return end c----------------------------------------------------------------------- program diagrami ! Diagrammer for IDL and c Program by Mitchell R Grunes. c Revision date: 5/15/2017. ! PV-WAVE character*5000 FilNam,FilNam2,aRd FilNam=aRd('IDL source file Name') FilNam2=aRd('Output file (blank=screen)') LCol=iRd('Column in which to write line #''s'// & '(0 for none; 80?)',0) iGraphics=iRd('Use IBM PC graphics characters (0=no)',0) iWarnEnd=iRd('Should I warn if "end" ends if, for... (0=no)',0) MaxL=iRd('Maximum line length without warning(160?)',160) iWarnUQ=iRd('Should I warn about unclosed quotes(0=no)',0) call diagram(FilNam,FilNam2,LCol,iGraphics, & iWarnEnd,iWarnUQ,MaxL) end c----------------------------------------------------------------------- subroutine diagram(FilNam,FilNam2,LCol,iGraphics,iWarnEnd, & iWarnUQ,MaxL) c Program by Mitchell R Grunes. c Revision date: 6/16/20. character*5000 FilNam,FilNam2 character*5000 a,b character*5 form character*8 fm character*1 c logical find common icol,icol1 logical fout open(1,file=FilNam,status='old') fout=FilNam2.gt.' ' if(fout)open(2,file=FilNam2,status='unknown') ! ASCII 12 is a form feed if(fout)write(2,*)char(12), & '=============--',FilNam(1:LenA(FilNam)),'--=============' if(fout) write(2,'(11x,a50,a30,/)') ! Write column header & '....,....1....,....2....,....3....,....4....,....5', & '....,....6....,....7....,....8' if(.not.fout)write(*,'(11x,a50,a30,/)') & '....,....1....,....2....,....3....,....4....,....5', & '....,....6....,....7....,....8' i1=0 ! # nest levels before ! current line i2=0 ! # nest levels on ! current line i3=0 ! # of nest levels after ! current line i4=0 ! not 0 to flag start or end ! of block InSub=0 ! Inside a subroutine or ! function? nMain=0 ! no mainline program yet InCase=0 ! not inside case iContinue=0 ! not continued from prior line nLine=0 icomment=0 ! Not inside comment - since IDL ! doesn't have /* and */, is always ! true iUnit=1 ! Read line from input file... 10 if(iRdLin(iUnit,fOut,MaxL,a,nLine,form).ne.0)goto 99 b=a icomment2=0 ! anything outside comment? icomment3=icomment ! no comment occurred? i=1 j=1 a=' ' ! Pre-processing iquote=0 ! no ' yet idquote=0 ! no " yet j=1 do i=1,LenA(b) c=b(i:i) if(c.ge.'A'.and.c.le.'Z')c=char(ichar(c)+32) if(c.eq.';'.and.iquote.eq.0.and.idquote.eq.0)then ! comment icomment3=1 goto 15 endif if(c.ne.' ')icomment2=1 if(c.eq.'@'.and.i.eq.1)goto 15 ! other procedure includes if(c.eq.''''.and.idquote.eq.0)then iquote=1-iquote c=' ' endif if(c.eq.'"' .and.iquote .eq.0)idquote=1-idquote if(iquote.ne.0.or.idquote.ne.0)c=' ' if(j.gt.1)then ! (kill multiple spaces) if(c.eq.' '.and.a(j-1:j-1).eq.' ')j=j-1 endif if(c.eq.':')then ! (put space after :) if(j.le.5000) a(j:j)=':' j=j+1 c=' ' endif if(j.le.5000) a(j:j)=c j=j+1 enddo 15 if((iQuote.ne.0.or.idquote.ne.0).and.iWarnUQ.ne.0) & call Errr('unclosed quote',form,fout,b) i2=i1 i3=i1 i4=0 igoto=0 ! no goto on line if(a.ne.' '.and.InSub.eq.0..and..not. & (find(a,'function ',2).or.find(a,'pro ',2)))then ! mainline InSub=InSub+1 nMain=nMain+1 if(fout)print*,'Line ',form,' ',b(1:LenA(b)) if(nMain.gt.1) & call Errr('Too many mainlines',form,fout,b) i2=i2+1 i3=i3+1 endif if(find(a, 'goto', 8+32).or.find(a,'return', 1+128))igoto=1 if(find(a, 'endif ', 2) .or.find(a,'endfor ', 2) & .or.find(a,'endelse ',2) .or.find(a,'endwhile ',2) & .or.find(a,'endcase ',2) .or.find(a,'endrep ', 2))then i3=i3-1 if(find(a,'begin ',1))then i3=i3+1 i4=max(i4,1) endif if(i3.lt.InCase)InCase=0 elseif(find(a,'case ',1).or.find(a,'begin ',1))then InCase=i1 i2=i2+1 i3=i3+1 i4=max(i4,1) if(find(a,': begin ',0))i4=max(i4,2) if(find(a,'end ',1))i3=i3-1 elseif(find(a,'end ',2))then if(i3.gt.0.or.Insub.gt.0)then ! Problem: IDL end may i3=i3-1 ! actually be an endif, ! endelse, etc. if(i3.eq.0.and.InSub.ne.0)InSub=0 if(i3.ne.0.and.iWarnEnd.ne.0) & call Warn('end type isn''t specific',form,fout,a) endif if(i3.lt.InCase)InCase=0 elseif(find(a,'function ',2).or.find(a,'pro ',2))then if(fout)print*,'Line ',form,' ',b(1:LenA(b)) InSub=InSub+1 i2=i2+1 i3=i3+1 if(InSub.ne.1.or.i3.ne.1)then call Errr('Invalid diagramming index',form,fout,b) i3=1 InSub=1 endif elseif((find(a,': ',0).or.find(a,':',256)).and. & InCase.ne.0)then ! simple case instances i4=max(i4,1) elseif((find(a,':',0).and.InCase.ne.0))then !other case instances ileft=0 iright=0 ileft2=0 iright2=0 do i=1,icol1 if(a(i:i).eq.'(')ileft=ileft+1 if(a(i:i).eq.')')iright=iright+1 if(a(i:i).eq.'[')ileft2=ileft+1 if(a(i:i).eq.']')iright2=iright+1 enddo if(ileft.eq.iright.and.ileft2.eq.iright2.and.icontinue.eq.0) & i4=max(i4,1) endif icontinue=0 if(find(a,'$ ',0))icontinue=1 nColPre=0 i1pp=0 i2pp=0 i3pp=0 i4pp=0 call FormLine(b,fout,nColPre,i1,i2,i3,i4, & i1pp,i2pp,i3pp,i4pp,igoto,LCol,form,icomment,icomment2, & icomment3,iGraphics) goto 10 99 if(i3.gt.0.or.InSub.ne.0) & call Errr('Nest levels left hanging at end',form,fout,b) end