IMPLEMENTATION MODULE DVIReader; (* Author: Andrew Trevorrow Implementation: University of Hamburg Modula-2 under VAX/VMS version 4 Date Started: August, 1984 Description: Implements routines and data structures for use in a TeX82 DVI translator. Much of the code in DVIReader is based on DVITYPE 2.7 by Donald Knuth. DVITYPE is a program for verifying a DVI file and also serves as a model for other DVI-reading programs. See the "TeXWARE" manual by Knuth for a complete description of DVITYPE and the format of DVI files. For efficiency reasons we assume the given DVI file is formatted correctly; it is the job of DVITYPE to diagnose bad DVI files. Revised: August, 1986 - PSDVI requires that MoveToDVIPage no longer assumes InterpretPage has been called after any previous MoveTo... routine. December, 1986 - Initialize fontexists flag to FALSE when reading postamble. June--August, 1988 (while at Aston University) - Import hoffset and voffset from Options to handle shifting of page. *) FROM SYSTEM IMPORT ADDRESS, (* byte address *) ADR, BYTE; FROM Storage IMPORT ALLOCATE, DEALLOCATE; (* need for NEW and DISPOSE *) FROM VMS IMPORT SYS$OPEN, SYS$CRMPSC, SYS$DASSGN, SYS$DELTVA; FROM SSDefinitions IMPORT SS$_ENDOFFILE; FROM SECDefinitions IMPORT SEC$V_EXPREG; FROM RMS IMPORT FAB, InitFab, FOPset, FOPtype, FACset, FACtype, SHRset, SHRtype; (* DEBUG (* DVIReader will only do terminal output while debugging. *) FROM TermOut IMPORT Write, WriteString, WriteLn, WriteInt, WriteCard, Halt; GUBED *) FROM Options IMPORT hoffset, voffset; (******************************************************************************* DECLARATIONS FOR RANDOMLY ACCESSING A DVI FILE A DVI file is considered to be an array of 8-bit bytes, ending with at least 4 223 bytes and having a total length divisible by 4. Under VAX/VMS a DVI file has fixed-length, 512-byte records (1 per block). The last record/s will be padded with 223 bytes to ensure that the above conditions hold. We will be randomly positioning to DVI bytes by setting DVIoffset, and reading bytes via GetDVIByte, SignedDVIByte etc. *) TYPE (* DVI file should never have more than MAX(INTEGER) bytes! *) DVIfile = ARRAY [0..MAX(INTEGER)] OF BYTE; DVIpointer = POINTER TO DVIfile; (* never allocated! *) VAR vas : ARRAY [0..1] OF ADDRESS; (* start and end virtual addresses *) DVIstart : DVIpointer; DVIoffset : CARDINAL; (* current byte offset in DVIfile *) channel : CARDINAL; (* fab.STV returned by SYS$OPEN *) gsdnam : ARRAY [0..42] OF CHAR; (* unused argument in SYS$CRPMSC *) status : CARDINAL; fab : FAB; postpostid : CARDINAL; (* offset of postpost's id byte *) (******************************************************************************) PROCEDURE OpenDVIFile (name : ARRAY OF CHAR); (* If the given file can be opened and is a valid TeX82 DVI file then we process the postamble and initialize currDVIpage and currTeXpage. *) VAR i : CARDINAL; BEGIN InitFab(fab); (* initialize fab *) WITH fab DO FNA := ADR(name); (* DVI file name *) FNS := BYTE(LEN(name)); (* bytes in file name *) FAC := FACset{FAC$BRO,FAC$GET}; (* read-only *) SHR := SHRset{SHR$GET}; (* share file with other readers *) FOP := FOPset{FOP$UFO}; (* need for SYS$CRMPSC *) RTV := BYTE(-1); (* for more efficient mapping *) END; status := SYS$OPEN(ADR(fab),0,0); (* open the file *) IF ODD(status) THEN WITH fab DO channel := STV; (* channel on which file is open *) END; (* now map entire DVI file into virtual address space *) vas[0] := 0; vas[1] := 0; status := SYS$CRMPSC (ADR(vas), (* starting and ending addresses *) ADR(vas), (* addresses returned *) 0, {SEC$V_EXPREG}, (* pages mapped into 1st available space *) gsdnam,0,0, channel, (* channel on which file has been opened *) 0,0,0, 36 (* large page fault cluster size *) ); IF status = SS$_ENDOFFILE THEN DVIErrorRoutine(DVIempty); (* given file is empty *) ELSIF NOT ODD(status) THEN (* DEBUG WriteString('SYS$CRMPSC failed! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); ELSE (* Now that the entire DVI file is mapped into virtual memory we can access any DVI byte as an offset from the address in vas[0]. *) DVIstart := vas[0]; (* move to last DVI byte *) DVIoffset := CARDINAL(ADDRESS(vas[1]) - ADDRESS(DVIstart)); (* check for trailing NULs first in case DVI file has come from non-VMS environment *) WHILE (DVIoffset > 0) AND (CARDINAL(DVIstart^[DVIoffset]) = 0) DO DEC(DVIoffset); (* skip NUL byte *) END; WHILE (DVIoffset > 0) AND (CARDINAL(DVIstart^[DVIoffset]) = 223) DO DEC(DVIoffset); (* skip 223 byte *) END; postpostid := DVIoffset; (* remember position of id byte *) IF GetDVIByte() <> 2 THEN (* DEBUG WriteString('Bad DVI file! id byte is not 2.'); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIbadid); (* not a valid TeX82 DVI file *) ELSE ProcessPostamble; (* get DVImag, totalpages, etc *) ProcessFontDefs; (* build and initialize font list *) currDVIpage := 0; (* we haven't processed a page yet *) FOR i := 0 TO 9 DO currTeXpage[i] := 0; END; END; END; ELSE DVIErrorRoutine(DVIunopened); (* given file could not be opened *) END; END OpenDVIFile; (******************************************************************************) (* Here are the functions used to get byte/s from DVIfile. They are essentially the same as those used in DVITYPE. *) PROCEDURE GetDVIByte () : INTEGER; (* Returns the value (unsigned) of the byte at DVIoffset and advances DVIoffset for the next GetDVIByte. *) VAR b : CARDINAL; BEGIN b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); RETURN b; END GetDVIByte; (******************************************************************************) PROCEDURE SignedDVIByte () : INTEGER; (* the next byte, signed *) VAR b : CARDINAL; BEGIN b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); IF b < 128 THEN RETURN b; ELSE RETURN b - 256; END; END SignedDVIByte; (******************************************************************************) PROCEDURE GetTwoDVIBytes () : INTEGER; (* the next 2 bytes, unsigned *) VAR a, b : CARDINAL; BEGIN a := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); RETURN a * 256 + b; END GetTwoDVIBytes; (******************************************************************************) PROCEDURE SignedDVIPair () : INTEGER; (* the next 2 bytes, signed *) VAR a, b : CARDINAL; BEGIN a := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); IF a < 128 THEN RETURN a * 256 + b; ELSE RETURN (a - 256) * 256 + b; END; END SignedDVIPair; (******************************************************************************) PROCEDURE GetThreeDVIBytes () : INTEGER; (* the next 3 bytes, unsigned *) VAR a, b, c : CARDINAL; BEGIN a := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); c := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); RETURN (a * 256 + b) * 256 + c; END GetThreeDVIBytes; (******************************************************************************) PROCEDURE SignedDVITrio () : INTEGER; (* the next 3 bytes, signed *) VAR a, b, c : CARDINAL; BEGIN a := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); c := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); IF a < 128 THEN RETURN (a * 256 + b) * 256 + c; ELSE RETURN ((a - 256) * 256 + b) * 256 + c; END; END SignedDVITrio; (******************************************************************************) PROCEDURE SignedDVIQuad () : INTEGER; (* the next 4 bytes, signed *) VAR a, b, c, d : CARDINAL; BEGIN a := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); b := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); c := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); d := CARDINAL(DVIstart^[DVIoffset]); INC(DVIoffset); IF a < 128 THEN RETURN ((a * 256 + b) * 256 + c) * 256 + d; ELSE RETURN (((a - 256) * 256 + b) * 256 + c) * 256 + d; END; END SignedDVIQuad; (******************************************************************************) PROCEDURE ProcessPostamble; (* Having successfully opened the DVI file, we find the postamble and initialize these global variables: lastbop, num, den, DVImag, maxstack, totalpages. The font definitions are read by ProcessFontDefs. *) VAR postamblepos, postamble, pagehtplusdp, pagewidth : CARDINAL; BEGIN DVIoffset := postpostid - 4; postamblepos := SignedDVIQuad(); (* get post_post's postamble ptr *) DVIoffset := postamblepos; postamble := GetDVIByte(); lastbop := SignedDVIQuad(); num := SignedDVIQuad(); den := SignedDVIQuad(); DVImag := SignedDVIQuad(); pagehtplusdp := SignedDVIQuad(); pagewidth := SignedDVIQuad(); maxstack := SignedDVIPair(); totalpages := SignedDVIPair(); IF maxstack > maxstacksize THEN (* DEBUG WriteString('Stack capacity exceeded! maxstack = '); WriteCard(maxstack); WriteString(' but maxstacksize only = '); WriteCard(maxstacksize); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIstackoverflow); (* now we don't need to test for stack overflow in DoPush *) END; (* DEBUG WriteString('postamble opcode ='); WriteInt(postamble); WriteLn; WriteString('postion of last bop ='); WriteInt(lastbop); WriteLn; WriteString('num ='); WriteInt(num); WriteLn; WriteString('den ='); WriteInt(den); WriteLn; WriteString('DVI mag ='); WriteInt(DVImag); WriteLn; WriteString('ht+dp of tallest page='); WriteInt(pagehtplusdp); WriteLn; WriteString('width of widest page ='); WriteInt(pagewidth); WriteLn; WriteString('max stack depth ='); WriteInt(maxstack); WriteLn; WriteString('total # of pages ='); WriteInt(totalpages); WriteLn; GUBED *) END ProcessPostamble; (******************************************************************************) PROCEDURE ProcessFontDefs; (* Read the fntdef commands in the postamble (fntdef commands in the DVI pages will be skipped) and store the information in the font list. (Note that complete fontspecs are NOT built here because DVIReader does not want to know about the format or naming conventions of font files; the client module must handle all this in its PixelTableRoutine.) Since ProcessPostamble ended by reading the totalpages parameter, the next GetDVIByte should return nop or first fntdef. *) VAR f, c, s, d, a, l : INTEGER; (* hold fntdef parameters *) i : INTEGER; ch : CHAR; (* for getting farea and fname *) farea, fname : fontstring; (* a and l bytes long respectively *) BEGIN totalfonts := 0; (* number of nodes in font list *) fontlist := NIL; REPEAT DVIcommand := GetDVIByte(); IF (DVIcommand >= fntdef1) AND (DVIcommand <= fntdef1+3) THEN CASE DVIcommand - fntdef1 OF 0 : f := GetDVIByte() | 1 : f := GetTwoDVIBytes() | 2 : f := GetThreeDVIBytes() | 3 : f := SignedDVIQuad() END; c := SignedDVIQuad(); (* checksum; ignore it *) s := SignedDVIQuad(); (* scaled size *) d := SignedDVIQuad(); (* design size *) a := GetDVIByte(); (* length of font area *) l := GetDVIByte(); (* length of font name *) farea := ''; FOR i := 0 TO a-1 DO (* read and store font area *) ch := CHR(GetDVIByte()); IF i < maxfontspec THEN farea[i] := ch END; END; fname := ''; FOR i := 0 TO l-1 DO (* read and store font name *) ch := CHR(GetDVIByte()); IF i < maxfontspec THEN fname[i] := ch END; END; NEW(currfont); WITH currfont^ DO fontused := FALSE; fontnum := f; scaledsize := s; designsize := d; fontarea := farea; fontarealen := CARDINAL(a); fontname := fname; fontnamelen := CARDINAL(l); fontspec := ''; fontspeclen := 0; (* fontspec has to be built by client *) fontexists := FALSE; (* becomes TRUE if fontspec can be opened *) totalchars := 0; charlist := NIL; (* first node allocated in DoFont *) chartail := NIL; (* nodes are added to tail of char list *) pixelptr := NIL; (* allocated once per font; see DoFont *) nextfont := fontlist; END; fontlist := currfont; (* add new font to head of list *) INC(totalfonts); ELSIF DVIcommand = nop THEN (* nop commands can occur between DVI commands *) ELSIF DVIcommand = postpost THEN (* we have reached end of postamble *) ELSE (* DEBUG WriteString('Unexpected DVI command in postamble = '); WriteCard(DVIcommand); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; UNTIL DVIcommand = postpost; END ProcessFontDefs; (******************************************************************************* DECLARATIONS FOR GETTING TO A DVI PAGE The user can select a particular page by specifying a DVI page number (from 1 to totalpages), or a TeX page number (based on the values of \count0,\count1,...,\count9), or simply requesting the next page in the DVI file (which depends on whether we are ascending or not). We will often need to follow the DVI backpointers to locate the bop byte of a selected page. *) VAR curreop, (* position of eop byte of current page *) currbop, (* position of bop byte of current page *) lastbop : CARDINAL; (* position of last bop byte *) prevbop : INTEGER; (* position of bop byte of previous page; note that prevbop of first page = -1 *) (******************************************************************************) PROCEDURE MoveToNextPage (ascending : BOOLEAN); (* Move to next DVI page; whether we can will depend on the current DVI page and if we are ascending or descending. *) BEGIN IF (currDVIpage = 1) AND (NOT ascending) THEN (* do nothing *) RETURN; ELSIF (currDVIpage = totalpages) AND ascending THEN (* do nothing *) RETURN; ELSIF currDVIpage = 0 THEN (* we haven't processed a page yet *) IF ascending THEN (* get first page *) ReadFirstBop; ELSE (* get last page *) currbop := lastbop; DVIoffset := currbop + 1; currDVIpage := totalpages; END; ELSE IF ascending THEN (* currently positioned after eop of currDVIpage, so get next bop *) ReadNextBop; ELSE (* move to bop pointed to by currbop's backpointer *) currbop := prevbop; DVIoffset := currbop + 1; (* move to byte after previous bop *) DEC(currDVIpage); END; END; ReadBopParameters; (* update currTeXpage and prevbop *) END MoveToNextPage; (******************************************************************************) PROCEDURE ReadFirstBop; (* Read first bop by skipping past preamble; update currbop and currDVIpage. *) VAR k, i, dummy : CARDINAL; BEGIN DVIoffset := 14; (* position of preamble's k parameter *) k := GetDVIByte(); (* length of x parameter *) FOR i := 1 TO k DO dummy := GetDVIByte(); (* skip preamble comment *) END; REPEAT (* skip any nops and fntdefs *) DVIcommand := GetDVIByte(); IF (DVIcommand = nop) OR (DVIcommand = bop) THEN (* do nothing *) ELSIF (DVIcommand >= fntdef1) AND (DVIcommand <= fntdef1+3) THEN SkipFntdef(DVIcommand - fntdef1); ELSE (* DEBUG WriteLn; WriteString('Unexpected DVI command before first bop = '); WriteCard(DVIcommand); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; UNTIL DVIcommand = bop; currbop := DVIoffset - 1; (* position in DVI file of first bop *) currDVIpage := 1; END ReadFirstBop; (******************************************************************************) PROCEDURE SkipFntdef (which : CARDINAL); (* Read past a fntdef command without interpreting it. *) VAR dummy, a, l, i : CARDINAL; BEGIN CASE which OF (* which = DVIcommand - fntdef1 *) 0 : dummy := GetDVIByte() | 1 : dummy := GetTwoDVIBytes() | 2 : dummy := GetThreeDVIBytes() | 3 : dummy := SignedDVIQuad() END; dummy := SignedDVIQuad(); dummy := SignedDVIQuad(); dummy := SignedDVIQuad(); a := GetDVIByte(); (* length of directory *) l := GetDVIByte(); (* length of font name *) FOR i := 0 TO l+a-1 DO dummy := GetDVIByte(); END; END SkipFntdef; (******************************************************************************) PROCEDURE ReadNextBop; (* We are currently positioned after an eop byte which we know is not the last. This routine positions us after the next bop byte and updates currbop and currDVIpage. *) BEGIN REPEAT (* skip any nops and fntdefs *) DVIcommand := GetDVIByte(); IF (DVIcommand = nop) OR (DVIcommand = bop) THEN (* do nothing *) ELSIF (DVIcommand >= fntdef1) AND (DVIcommand <= fntdef1+3) THEN SkipFntdef(DVIcommand - fntdef1); ELSE (* DEBUG WriteLn; WriteString('Unexpected DVI command between eop and bop = '); WriteCard(DVIcommand); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; UNTIL DVIcommand = bop; currbop := DVIoffset - 1; (* position in DVI file of this bop *) INC(currDVIpage); END ReadNextBop; (******************************************************************************) PROCEDURE ReadBopParameters; (* We should now be positioned after the bop of desired page, so read the 10 TeX counters and update currTeXpage and prevbop. At the end of this routine we will be at the byte after currbop's parameters and ready to InterpretPage. *) VAR i : CARDINAL; BEGIN FOR i := 0 TO 9 DO currTeXpage[i] := SignedDVIQuad(); END; prevbop := SignedDVIQuad(); (* position of previous bop in DVI file *) END ReadBopParameters; (******************************************************************************) PROCEDURE MoveToDVIPage (n : CARDINAL); (* Move to nth DVI page; n should be in 1..totalpages. *) BEGIN IF (n < 1) OR (n > totalpages) THEN (* do nothing *) RETURN; END; IF n = 1 THEN (* Note that this test must come before next ELSIF so that we avoid any problems when currDVIpage initially = 0. *) ReadFirstBop; (* We have removed the ELSIF code because it assumes InterpretPage is called after every MoveTo... routine (which PSDVI does NOT call when locating the first and final pages of a given subrange). ELSIF n = currDVIpage + 1 THEN ReadNextBop; *) ELSE IF n < currDVIpage THEN currbop := prevbop; (* start searching backwards from previous page *) DEC(currDVIpage); ELSIF n > currDVIpage THEN currbop := lastbop; (* start searching backwards from last page *) currDVIpage := totalpages; ELSE (* n = currDVIpage so we'll just move back to currbop *) END; (* n is now <= currDVIpage so search by following backpointers *) LOOP IF n = currDVIpage THEN DVIoffset := currbop + 1; (* move to byte after currbop *) EXIT; ELSE DVIoffset := currbop + 41; (* move to location of backpointer *) currbop := SignedDVIQuad(); (* get location of previous page *) DEC(currDVIpage); END; END; END; ReadBopParameters; (* update currTeXpage and prevbop *) END MoveToDVIPage; (******************************************************************************) PROCEDURE MoveToTeXPage (VAR newTeXpage : TeXpageinfo) (* in *) : BOOLEAN; (* Return TRUE iff the given TeX page exists. If so then we move to the lowest matching page. *) VAR savecurrbop, savecurrDVIpage : CARDINAL; nextbop : INTEGER; i : CARDINAL; atleastone : BOOLEAN; BEGIN (* save away current page and DVI position *) savecurrDVIpage := currDVIpage; IF currDVIpage <> 0 THEN (* only if we've processed a page *) savecurrbop := currbop; (* note that curreop is saved in last InterpretPage *) END; (* search backwards through all DVI pages for lowest matching page *) atleastone := FALSE; nextbop := lastbop; FOR i := totalpages TO 1 BY -1 DO DVIoffset := nextbop + 1; ReadBopParameters; (* update currTeXpage and prevbop *) IF CurrMatchesNew(newTeXpage) THEN currbop := nextbop; currDVIpage := i; atleastone := TRUE; END; nextbop := prevbop; END; IF NOT atleastone THEN (* no match, so restore currDVIpage *) currDVIpage := savecurrDVIpage; IF currDVIpage <> 0 THEN (* restore page and positioning info *) currbop := savecurrbop; DVIoffset := currbop + 1; ReadBopParameters; (* restore currTeXpage and prevbop *) DVIoffset := curreop + 1; (* we should now be after the eop byte of the original page *) END; RETURN FALSE; ELSE (* we found lowest matching page *) DVIoffset := currbop + 1; END; ReadBopParameters; (* update currTeXpage and prevbop *) RETURN TRUE; END MoveToTeXPage; (******************************************************************************) PROCEDURE CurrMatchesNew (VAR newTeXpage : TeXpageinfo) : BOOLEAN; (* Return TRUE iff currTeXpage matches newTeXpage. *) VAR i : [0..9]; BEGIN WITH newTeXpage DO FOR i := 0 TO lastvalue DO IF present[i] AND (value[i] <> currTeXpage[i]) THEN RETURN FALSE; END; END; END; RETURN TRUE; END CurrMatchesNew; (******************************************************************************* DECLARATIONS FOR INTERPRETING A DVI PAGE The commands between the bop and eop bytes for a particular page need to be translated (based on the method used by DVITYPE) before we can determine the the position and shape of all rules on that page, as well as the position of all characters and which fonts they belong to. *) CONST (* Use symbolic names for the opcodes of DVI commands: *) setchar0 = 0; (* setchar1..setchar127 = 1..127 *) set1 = 128; (* set2,set3,set4 = 129,130,131 *) setrule = 132; put1 = 133; (* put2,put3,put4 = 134,135,136 *) putrule = 137; nop = 138; bop = 139; eop = 140; push = 141; pop = 142; right1 = 143; w0 = 147; x0 = 152; down1 = 157; y0 = 161; z0 = 166; right2 = 144; w1 = 148; x1 = 153; down2 = 158; y1 = 162; z1 = 167; right3 = 145; w2 = 149; x2 = 154; down3 = 159; y2 = 163; z2 = 168; right4 = 146; w3 = 150; x3 = 155; down4 = 160; y3 = 164; z3 = 169; w4 = 151; x4 = 156; y4 = 165; z4 = 170; fntnum0 = 171; (* fntnum1..fntnum63 = 172..234 *) fnt1 = 235; (* fnt2,fnt3,fnt4 = 236,237,238 *) xxx1 = 239; (* xxx2,xxx3,xxx4 = 240,241,242 *) fntdef1 = 243; (* fntdef2,fntdef3,fntdef4 = 244,245,246 *) pre = 247; post = 248; postpost = 249; (* undefined commands = 250..255 *) maxint = 2147483647; (* SYSDEP: 2^31 - 1 *) maxstacksize = 100; (* maximum stack size for state values *) maxdrift = 2; (* prevent hh & vv from drifting too far *) VAR DVIcommand : [0..255]; (* holds next DVI command *) maxstack, (* max pushes over pops in DVI file *) num, (* DVI numerator *) den : CARDINAL; (* DVI denominator *) conv : REAL; (* converts DVI units to pixels *) h, v, (* current pos on page in DVI units *) w, x, (* horizontal increments in DVI units *) y, z, (* vertical increments in DVI units *) hh, vv, (* h and v in pixels *) hhh, vvv : INTEGER; (* h and v rounded to nearest pixel *) hstack, vstack, (* push down stacks for state values *) wstack, xstack, ystack, zstack, hhstack, vvstack : ARRAY [0..maxstacksize-1] OF INTEGER; stackpos : [0..maxstacksize]; (* stacks empty when stackpos = 0, i.e., top of stacks = stackpos - 1 *) fontspace : INTEGER; (* used in DoRight and DoDown *) thisrule : ruleinfoptr; (* temporary pointer to node in rulelist *) ruletail : ruleinfoptr; (* tail of rule information list *) thischar : charinfoptr; (* temporary pointer to node in charlist *) (******************************************************************************) PROCEDURE SetConversionFactor (resolution, magnification : CARDINAL); (* Client module must help calculate conv, the number of pixels per DVI unit. *) BEGIN conv := FLOAT(num)/254000.0 * FLOAT(resolution)/FLOAT(den) * FLOAT(magnification)/1000.0; END SetConversionFactor; (******************************************************************************) PROCEDURE InterpretPage; (* When this routine is called we are positioned after the bytes of a bop command (i.e., at currbop + 45). At the end of this routine we will be positioned after the eop byte for the current page. In between we carry out the important task of translating the DVI description of this page and filling in the various data structures exported by DVIReader. *) VAR param : INTEGER; BEGIN InitStateValues; InitPage; REPEAT DVIcommand := GetDVIByte(); (* For efficiency reasons the most frequent commands should be tested 1st. The following order is the result of frequency testing on "typical" DVI files. Note that the most frequent commands in the DVI file generated by TeX 1.3 for the Dec. 1983 LaTeX manual were: z4) AND (DVIcommand < fnt1) (* fntnum0..fntnum63 *) THEN DoFont(DVIcommand - fntnum0); (* catch all the remaining movement commands *) ELSIF (DVIcommand > pop) AND (DVIcommand < fntnum0) THEN IF DVIcommand = right2 THEN DoRight(SignedDVIPair()); ELSIF DVIcommand = right4 THEN DoRight(SignedDVIQuad()); ELSIF DVIcommand = x2 THEN x := SignedDVIPair(); DoRight(x); ELSIF DVIcommand = x3 THEN x := SignedDVITrio(); DoRight(x); ELSIF DVIcommand = down3 THEN DoDown(SignedDVITrio()); ELSIF DVIcommand = down4 THEN DoDown(SignedDVIQuad()); ELSIF DVIcommand = w2 THEN w := SignedDVIPair(); DoRight(w); ELSIF DVIcommand = z0 THEN DoDown(z); ELSIF DVIcommand = y3 THEN y := SignedDVITrio(); DoDown(y); ELSIF DVIcommand = z3 THEN z := SignedDVITrio(); DoDown(z); ELSIF DVIcommand = down2 THEN DoDown(SignedDVIPair()); (* the next DVI commands are used very rarely (by TeX 1.3 at least) *) ELSIF DVIcommand = w1 THEN w := SignedDVIByte(); DoRight(w); ELSIF DVIcommand = w4 THEN w := SignedDVIQuad(); DoRight(w); ELSIF DVIcommand = x1 THEN x := SignedDVIByte(); DoRight(x); ELSIF DVIcommand = x4 THEN x := SignedDVIQuad(); DoRight(x); ELSIF DVIcommand = y1 THEN y := SignedDVIByte(); DoDown(y); ELSIF DVIcommand = y2 THEN y := SignedDVIPair(); DoDown(y); ELSIF DVIcommand = y4 THEN y := SignedDVIQuad(); DoDown(y); ELSIF DVIcommand = z1 THEN z := SignedDVIByte(); DoDown(z); ELSIF DVIcommand = z2 THEN z := SignedDVIPair(); DoDown(z); ELSIF DVIcommand = z4 THEN z := SignedDVIQuad(); DoDown(z); ELSIF DVIcommand = right1 THEN DoRight(SignedDVIByte()); ELSIF DVIcommand = down1 THEN DoDown(SignedDVIByte()); ELSE (* DEBUG (* will only occur if we've missed a movement command *) WriteLn; WriteString('Bug in InterpretPage!'); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; ELSIF DVIcommand = setrule THEN DoSetRule(SignedDVIQuad(),SignedDVIQuad()); ELSIF DVIcommand = putrule THEN DoPutRule(SignedDVIQuad(),SignedDVIQuad()); ELSIF (DVIcommand >= put1) AND (DVIcommand <= put1+3) THEN CASE DVIcommand - put1 OF 0 : DoPutChar(GetDVIByte()) | 1 : DoPutChar(GetTwoDVIBytes()) | 2 : DoPutChar(GetThreeDVIBytes()) | 3 : DoPutChar(SignedDVIQuad()) END; ELSIF (DVIcommand >= set1) AND (DVIcommand <= set1+3) THEN CASE DVIcommand - set1 OF 0 : DoSetChar(GetDVIByte()) | 1 : DoSetChar(GetTwoDVIBytes()) | 2 : DoSetChar(GetThreeDVIBytes()) | 3 : DoSetChar(SignedDVIQuad()) END; ELSIF (DVIcommand >= fnt1) AND (DVIcommand <= fnt1+3) THEN CASE DVIcommand - fnt1 OF 0 : DoFont(GetDVIByte()) | 1 : DoFont(GetTwoDVIBytes()) | 2 : DoFont(GetThreeDVIBytes()) | 3 : DoFont(SignedDVIQuad()) END; ELSIF (DVIcommand >= xxx1) AND (DVIcommand <= xxx1+3) THEN CASE DVIcommand - xxx1 OF 0 : param := GetDVIByte() | 1 : param := GetTwoDVIBytes() | 2 : param := GetThreeDVIBytes() | 3 : param := SignedDVIQuad() END; (* Pass current pixel position, number of bytes and byte grabbing function for client to use. We use IgnoreSpecial if client does not assign a procedure. *) SpecialRoutine(hh, vv, param, GetDVIByte); (* skip fntdef command since we've got this info from postamble *) ELSIF (DVIcommand >= fntdef1) AND (DVIcommand <= fntdef1+3) THEN SkipFntdef(DVIcommand - fntdef1); ELSIF DVIcommand = nop THEN (* do nothing *) ELSIF DVIcommand = eop THEN (* do nothing *) ELSE (* DEBUG WriteLn; WriteString('Unexpected DVI command while interpreting page = '); WriteCard(DVIcommand); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; UNTIL DVIcommand = eop; (* save position of eop byte for use in MoveToTeXPage *) curreop := DVIoffset - 1; IF stackpos <> 0 THEN (* DEBUG WriteString('Stack not empty at eop!'); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; pageempty := (minhp = maxint) AND (minvp = maxint) AND (maxhp = -maxint) AND (maxvp = -maxint); (* InitPage values *) END InterpretPage; (******************************************************************************) PROCEDURE InitStateValues; (* Initialize the state values and stack. *) BEGIN hh := hoffset; (* 0 if no horizontal shift specified *) vv := voffset; (* 0 if no vertical shift specified *) IF hoffset >= 0 THEN h := TRUNC(FLOAT(hoffset) / conv + 0.5); ELSE h := - TRUNC(FLOAT(ABS(hoffset)) / conv + 0.5); END; IF voffset >= 0 THEN v := TRUNC(FLOAT(voffset) / conv + 0.5); ELSE v := - TRUNC(FLOAT(ABS(voffset)) / conv + 0.5); END; w := 0; x := 0; y := 0; z := 0; stackpos := 0; fontspace := 0; (* for DoRight and DoDown before a DoFont call *) END InitStateValues; (******************************************************************************) PROCEDURE InitPage; (* Initialize page structures so there are no fonts, no chars and no rules. *) BEGIN (* page edges will change if there is at least one char or rule on page *) minhp := maxint; minvp := maxint; maxhp := -maxint; maxvp := -maxint; currfont := fontlist; WHILE currfont <> NIL DO WITH currfont^ DO IF fontused THEN (* only reset those fonts used in last page *) fontused := FALSE; totalchars := 0; (* deallocate char list completely; DoFont will allocate first node *) WHILE charlist <> NIL DO thischar := charlist; charlist := thischar^.nextchar; DISPOSE(thischar); END; chartail := NIL; (* pixel table remains allocated *) END; currfont := nextfont; END; END; currfont := NIL; (* current font is undefined at start of page *) totalrules := 0; (* deallocate rule information except for one node (for DoSet/PutRule) *) WHILE rulelist <> ruletail DO thisrule := rulelist; rulelist := thisrule^.nextrule; DISPOSE(thisrule); END; rulelist^.rulecount := 0; (* no rules in this node *) rulelist^.nextrule := NIL; END InitPage; (******************************************************************************) PROCEDURE DoSetChar (ch : CARDINAL); (* Add char info to current chartable, update our horizontal position on the page and check the page edges. *) BEGIN WITH currfont^ DO IF ch > maxTeXchar THEN DVIErrorRoutine(DVIbadchar); RETURN; (* ignore ch *) END; WITH chartail^ DO IF charcount = chartablesize THEN (* allocate a new chartable *) NEW(nextchar); (* add new node to end of char list *) nextchar^.charcount := 0; (* reset charcount *) nextchar^.nextchar := NIL; chartail := nextchar; END; END; WITH chartail^ DO (* may be new chartable *) WITH chartable[charcount] DO hp := hh; vp := vv; code := ch; END; WITH pixelptr^[ch] DO (* do page edges increase? *) IF vv - yo < minvp THEN minvp := vv - yo END; IF hh - xo < minhp THEN minhp := hh - xo END; IF vv + (ht - yo - 1) > maxvp THEN maxvp := vv + (ht - yo - 1) END; IF hh + (wd - xo - 1) > maxhp THEN maxhp := hh + (wd - xo - 1) END; (* the above checks ensure that page edges include all black pixels in glyph, but we also want to include reference point *) IF hh < minhp THEN minhp := hh END; IF vv < minvp THEN minvp := vv END; IF hh > maxhp THEN maxhp := hh END; IF vv > maxvp THEN maxvp := vv END; (* add pixel width calculated in PixelTableRoutine *) hh := hh + pwidth; (* use hhh and maxdrift to prevent hh drifting too far from h *) hhh := PixelRound(h + dwidth); IF ABS(hhh - hh) > maxdrift THEN IF hhh > hh THEN hh := hhh - maxdrift; ELSE hh := hhh + maxdrift; END; END; (* add DVI width calculated in PixelTableRoutine *) h := h + dwidth; END; INC(totalchars); INC(charcount); END; END; END DoSetChar; (******************************************************************************) PROCEDURE DoPutChar (ch : CARDINAL); (* Exactly the same as DoSetChar, but we DON'T update the horizontal position on the page. (We still have to check page edges.) *) BEGIN WITH currfont^ DO IF ch > maxTeXchar THEN DVIErrorRoutine(DVIbadchar); RETURN; (* ignore ch *) END; WITH chartail^ DO IF charcount = chartablesize THEN (* allocate a new chartable *) NEW(nextchar); (* add new node to end of char list *) nextchar^.charcount := 0; (* reset charcount *) nextchar^.nextchar := NIL; chartail := nextchar; END; END; WITH chartail^ DO (* may be new chartable *) WITH chartable[charcount] DO hp := hh; vp := vv; code := ch; END; WITH pixelptr^[ch] DO (* do page edges increase? *) IF vv - yo < minvp THEN minvp := vv - yo END; IF hh - xo < minhp THEN minhp := hh - xo END; IF vv + (ht - yo - 1) > maxvp THEN maxvp := vv + (ht - yo - 1) END; IF hh + (wd - xo - 1) > maxhp THEN maxhp := hh + (wd - xo - 1) END; (* the above checks ensure that page edges include all black pixels in glyph, but we also want to include reference point *) IF hh < minhp THEN minhp := hh END; IF vv < minvp THEN minvp := vv END; IF hh > maxhp THEN maxhp := hh END; IF vv > maxvp THEN maxvp := vv END; END; INC(totalchars); INC(charcount); END; END; END DoPutChar; (******************************************************************************) PROCEDURE PixelRound (DVIunits : INTEGER) : INTEGER; (* Return the nearest number of pixels in the given DVI dimension. *) BEGIN IF DVIunits > 0 THEN RETURN TRUNC(conv * FLOAT(DVIunits) + 0.5); ELSE RETURN - TRUNC(conv * FLOAT(ABS(DVIunits)) + 0.5); END; END PixelRound; (******************************************************************************) PROCEDURE DoPush; (* Push state values onto stack. No need to test for stack overflow since we compare maxstack and maxstacksize in ProcessPostamble. *) BEGIN hstack[stackpos] := h; vstack[stackpos] := v; wstack[stackpos] := w; xstack[stackpos] := x; ystack[stackpos] := y; zstack[stackpos] := z; hhstack[stackpos] := hh; vvstack[stackpos] := vv; INC(stackpos); (* stackpos = next vacant position in stacks *) END DoPush; (******************************************************************************) PROCEDURE DoPop; (* Pop state values from top of stack. *) BEGIN (* DEBUG IF stackpos = 0 THEN WriteString('Stack empty!'); WriteLn; Halt(2); END; GUBED *) DEC(stackpos); h := hstack[stackpos]; v := vstack[stackpos]; w := wstack[stackpos]; x := xstack[stackpos]; y := ystack[stackpos]; z := zstack[stackpos]; hh := hhstack[stackpos]; vv := vvstack[stackpos]; END DoPop; (******************************************************************************) PROCEDURE DoRight (amount : INTEGER); (* Move the reference point horizontally by given amount (usually +ve). When the amount is small, like a kern, hh changes by rounding the amount; but when the amount is large, hh changes by rounding the true position h so that accumulated rounding errors disappear. *) BEGIN IF (amount < fontspace) AND (amount > -4 * fontspace) THEN hh := hh + PixelRound(amount); (* use hhh and maxdrift to prevent hh drifting too far from h *) hhh := PixelRound(h + amount); IF ABS(hhh - hh) > maxdrift THEN IF hhh > hh THEN hh := hhh - maxdrift; ELSE hh := hhh + maxdrift; END; END; ELSE hh := PixelRound(h + amount); END; h := h + amount; END DoRight; (******************************************************************************) PROCEDURE DoDown (amount : INTEGER); (* Move the reference point vertically by given amount (usually +ve). Rounding is done similarly to DoRight but with the threshold between small and large amounts increased by a factor of 5. *) BEGIN IF ABS(amount) < 5 * fontspace THEN vv := vv + PixelRound(amount); (* use vvv and maxdrift to prevent vv drifting too far from v *) vvv := PixelRound(v + amount); IF ABS(vvv - vv) > maxdrift THEN IF vvv > vv THEN vv := vvv - maxdrift; ELSE vv := vvv + maxdrift; END; END; ELSE vv := PixelRound(v + amount); END; v := v + amount; END DoDown; (******************************************************************************) PROCEDURE DoSetRule (height, width : INTEGER); (* Add rule information to current ruletable, update page edges, h and hh (but only if width and height are > 0). *) BEGIN IF (height > 0) AND (width > 0) THEN WITH ruletail^ DO IF rulecount = ruletablesize THEN (* allocate a new ruletable *) NEW(nextrule); (* add new node to end of rule list *) nextrule^.rulecount := 0; (* reset rulecount *) nextrule^.nextrule := NIL; ruletail := nextrule; END; END; WITH ruletail^ DO (* may be new ruletable *) WITH ruletable[rulecount] DO hp := hh; vp := vv; wd := RulePixels(width); ht := RulePixels(height); (* do page edges increase? *) IF vv - (ht - 1) < minvp THEN minvp := vv - (ht - 1) END; IF hh + (wd - 1) > maxhp THEN maxhp := hh + (wd - 1) END; (* ref pt of rule is bottom left black pixel *) IF vv > maxvp THEN maxvp := vv END; IF hh < minhp THEN minhp := hh END; hh := hh + wd; (* use hhh and maxdrift to prevent hh drifting too far from h *) hhh := PixelRound(h + width); IF ABS(hhh - hh) > maxdrift THEN IF hhh > hh THEN hh := hhh - maxdrift; ELSE hh := hhh + maxdrift; END; END; h := h + width; END; INC(totalrules); INC(rulecount); END; END; END DoSetRule; (******************************************************************************) PROCEDURE DoPutRule (height, width : INTEGER); (* Exactly the same as DoSetRule, but we DON'T update the horizontal position on the page. (We still have to check page edges.) *) BEGIN IF (height > 0) AND (width > 0) THEN WITH ruletail^ DO IF rulecount = ruletablesize THEN (* allocate a new ruletable *) NEW(nextrule); (* add new node to end of rule list *) nextrule^.rulecount := 0; (* reset rulecount *) nextrule^.nextrule := NIL; ruletail := nextrule; END; END; WITH ruletail^ DO (* may be new ruletable *) WITH ruletable[rulecount] DO hp := hh; vp := vv; wd := RulePixels(width); ht := RulePixels(height); (* do page edges increase? *) IF vv - (ht - 1) < minvp THEN minvp := vv - (ht - 1) END; IF hh + (wd - 1) > maxhp THEN maxhp := hh + (wd - 1) END; (* ref pt of rule is bottom left black pixel *) IF vv > maxvp THEN maxvp := vv END; IF hh < minhp THEN minhp := hh END; END; INC(totalrules); INC(rulecount); END; END; END DoPutRule; (******************************************************************************) PROCEDURE RulePixels (DVIunits : INTEGER) : INTEGER; (* Return the number of pixels in the given height or width of a rule using the method recommended in DVITYPE. *) VAR n : INTEGER; BEGIN n := TRUNC(conv * FLOAT(DVIunits)); IF FLOAT(n) < conv * FLOAT(DVIunits) THEN RETURN n + 1 ELSE RETURN n END; END RulePixels; (******************************************************************************) PROCEDURE DoFont (externf : INTEGER); (* Search font list for externf, setting currfont and fontspace. If this is the first time we've seen this font (on current page) then we need to allocate the first chartable. If this is the first time we've seen this font used at all then we allocate a pixeltable and call client routine to fill it in. *) BEGIN currfont := fontlist; WHILE (currfont <> NIL) AND (currfont^.fontnum <> externf) DO currfont := currfont^.nextfont; END; IF currfont = NIL THEN (* DEBUG WriteLn; WriteString('Failed to find font #'); WriteInt(externf); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; WITH currfont^ DO IF fontused THEN (* do nothing since we've already used this font on this page *) ELSE fontused := TRUE; NEW(charlist); (* allocate first chartable *) WITH charlist^ DO charcount := 0; (* for DoSet/PutChar *) nextchar := NIL; (* this node is also last *) END; chartail := charlist; IF pixelptr = NIL THEN (* first time we've seen this font requested *) NEW(pixelptr); PixelTableRoutine; (* call client routine to build pixel table *) END; END; fontspace := scaledsize DIV 6; (* See DVITYPE; a 3-unit thin space. Note that a thin space is 1/6 of a quad, where a quad is 1 em in the current font and usually equals the design size. *) END; END DoFont; (******************************************************************************) PROCEDURE IgnoreSpecial(xpos, ypos, (* in *) specialbytes : INTEGER; (* in *) GetNextByte : GetByteFunction); (* in *) (* Default SpecialRoutine simply skips bytes given to TeX's \special command. *) VAR i, unused : INTEGER; BEGIN FOR i := 1 TO specialbytes DO unused := GetNextByte(); END; END IgnoreSpecial; (******************************************************************************) PROCEDURE SortFonts (VAR unusedlist : fontinfoptr); (* out *) (* Sort fontlist in order of ascending totalchars. Fonts with least characters can then be accessed first. Since the number of fonts used on a typical page is quite small, a simple sorting algorithm should be good enough. Note that unused fonts are moved to the end of the list and unusedlist points to the first such node. *) VAR newfontlist, prevfont, largest, prevlargest : fontinfoptr; mostchars : CARDINAL; BEGIN newfontlist := NIL; (* go thru fontlist once and move all unused fonts to head of newfontlist *) prevfont := NIL; currfont := fontlist; WHILE currfont <> NIL DO WITH currfont^ DO IF fontused THEN prevfont := currfont; (* remember previous node *) currfont := nextfont; ELSE (* move node from fontlist to head of newfontlist and don't change prevfont *) IF prevfont = NIL THEN fontlist := nextfont; (* remove first node in fontlist *) nextfont := newfontlist; newfontlist := currfont; currfont := fontlist; ELSE prevfont^.nextfont := nextfont; nextfont := newfontlist; newfontlist := currfont; currfont := prevfont^.nextfont; END; END; END; END; (* unusedlist will be last unused font moved to newfontlist. It will be NIL if either fontlist is NIL or all fonts are used. *) unusedlist := newfontlist; (* Now go thru fontlist repeatedly moving node with max totalchars to head of newfontlist until fontlist is exhausted. *) WHILE fontlist <> NIL DO prevfont := NIL; currfont := fontlist; prevlargest := NIL; largest := fontlist; mostchars := 0; WHILE currfont <> NIL DO (* search for largest totalchars *) WITH currfont^ DO IF totalchars > mostchars THEN prevlargest := prevfont; largest := currfont; mostchars := totalchars; END; prevfont := currfont; currfont := nextfont; END; END; (* move largest node from fontlist to head of newfontlist *) WITH largest^ DO IF prevlargest = NIL THEN fontlist := nextfont; (* remove first node in fontlist *) ELSE prevlargest^.nextfont := nextfont; END; nextfont := newfontlist; newfontlist := largest; END; END; fontlist := newfontlist; (* used fonts now sorted and unused fonts at end *) END SortFonts; (******************************************************************************) PROCEDURE CloseDVIFile; (* Close the currently open DVI file and deallocate dynamic data structures. *) BEGIN status := SYS$DELTVA(ADR(vas),ADR(vas),0); IF NOT ODD(status) THEN (* DEBUG WriteString('SYS$DELTVA failed! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; status := SYS$DASSGN(channel); IF NOT ODD(status) THEN (* DEBUG WriteString('SYS$DASSGN failed! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) DVIErrorRoutine(DVIcatastrophe); END; WHILE fontlist <> NIL DO currfont := fontlist; WITH currfont^ DO WHILE charlist <> NIL DO (* deallocate char list *) thischar := charlist; charlist := thischar^.nextchar; DISPOSE(thischar); END; IF pixelptr <> NIL THEN DISPOSE(pixelptr); (* deallocate pixel table *) END; fontlist := nextfont; END; DISPOSE(currfont); (* deallocate font information *) END; (* Deallocate rule information except for one node (in case client opens another DVI file). *) WHILE rulelist <> ruletail DO thisrule := rulelist; rulelist := thisrule^.nextrule; DISPOSE(thisrule); END; END CloseDVIFile; (******************************************************************************) BEGIN totalrules := 0; NEW(rulelist); (* for first InitPage *) ruletail := rulelist; (* ditto *) fontlist := NIL; (* safer for CloseDVIFile *) SpecialRoutine := IgnoreSpecial; (* client can reassign *) END DVIReader.