IMPLEMENTATION MODULE FontReader; (* Author: Andrew Trevorrow Implementation: University of Hamburg Modula-2 under VAX/VMS version 4 Date Started: May, 1985 Description: This module can extract font information from PXL, PK or TFM files. (GF files are not handled; it is assumed that sites with GF files will decide to convert them to PK files sooner or later!) Each type of font file is considered to be an array of 8-bit bytes. Only one font file is open at any time. We move to byte positions using byteoffset and read bytes and words using GetByte, SignedQuad, etc. Revised: June, 1985 - Use Halt(2) instead of HALT. August, 1985 - Use ScreenIO routines when debugging. September, 1985 - Added GetPXLGlyph and associated glyph cacheing code. October, 1985 - Removed above cacheing stuff! Now use SYS$CRMPSC to map an entire PXL file into virtual memory where it is treated as an array of bytes. March, 1986 - Amendments to Modula-2 language required a few minor syntactic changes. November, 1986 - PXLReader has been expanded and is now called FontReader. All font-dependent code has been moved out of PSDVI's main module. A new font format can be handled just by adding code to FontReader. - Reduced page fault cluster size from 36 to 16 because PK files are smaller. - Always start fontspec with fontdir; fontarea is really only for TFM files. December, 1986 - GetBitmap now called LoadBitmap and uses Put routines from PSWriter to send bitmap and metric info directly to output file. November, 1987 (while at The Open University) - Added charsperline code to LoadBitmap routines so that output lines don't get too long. - Added code to handle PostScript fonts (for which only TFM files exist). BuildFontSpec now checks for a fontname beginning with "PS-" and sets the font's psfont flag. If TRUE then we must construct a TFM filespec (starting with tfmdir or fontarea if fontarealen > 0) and later fill the font's pixeltable with character info from that TFM file. - Renamed ConvertTFMWidth to FixToDVI. - PXL/PKFillPixelTable now call TFMFillPixelTable if the font is a PostScript font (and its TFM file could be opened). June--August, 1988 (while at Aston University) - Now use /psprefix value to check for a PostScript font. - Changed BuildFontSpec so that the fontsize substring no longer has to be the same length in all font files. September--October, 1989 (while at Aston University, 2nd time) - Fixed bug reported by Niel Kempson in FixToDVI. *) FROM SYSTEM IMPORT ADDRESS, ADR, BYTE, WORD; FROM VMS IMPORT SYS$OPEN, SYS$CRMPSC, SYS$DASSGN, SYS$DELTVA; FROM SECDefinitions IMPORT SEC$V_EXPREG; FROM RMS IMPORT FAB, InitFab, FOPset, FOPtype, FACset, FACtype, SHRset, SHRtype; FROM FileSystem IMPORT File, Open, Done, Close; FROM Options IMPORT psprefix, tfmdir, fontdir, dummyfont, mag, resolution, Cap; FROM DVIReader IMPORT (* CONST *) maxfontspec, maxTeXchar, (* TYPE *) fontstring, fontinfo, fontinfoptr, pixeltable, pixeltableptr, (* VAR *) currfont, (* PROCEDURE *) PixelRound; FROM PSWriter IMPORT Put, PutString, PutInt, PutCard; FROM TermOut IMPORT WriteString, WriteCard, WriteInt, WriteLn, Halt; CONST NULL = 0C; (* SYSDEP: used to terminate a string if not full *) CR = 15C; (* used in LoadBitmap *) TYPE (* font files should never have more than MAX(INTEGER) bytes! *) fontfile = ARRAY [0..MAX(INTEGER)] OF BYTE; filepointer = POINTER TO fontfile; (* never allocated! *) VAR vas : ARRAY [0..1] OF ADDRESS; (* start and end virtual addresses *) filestart : filepointer; (* pointer to starting address of file *) byteoffset, (* byte offset from start of file *) channel : CARDINAL; (* fab.STV returned by SYS$OPEN *) gsdnam : ARRAY [0..42] OF CHAR; (* unused argument in SYS$CRPMSC *) status : CARDINAL; fab : FAB; psprefixlen, (* length of psprefix string *) fontdirlen, (* length of fontdir string *) dummyfontlen : CARDINAL; (* length of dummyfont string *) formatstr : ARRAY [0..2] OF CHAR; (* PXL or PK *) formatlen : CARDINAL; (* 3 or 2 *) xfactor : REAL; (* resolution/200 or resolution/1000 *) hexdigs : ARRAY [0..15] OF CHAR; (* 0..9ABCDEF for LoadBitmap *) gpower : ARRAY [0..8] OF BITSET; (* 0,1,11,111,1111,...,11111111 *) CompleteFontSpec : (* used by BuildFontSpec *) PROCEDURE (fontinfoptr, CARDINAL, CARDINAL, VAR CARDINAL) : BOOLEAN; (******************************************************************************) PROCEDURE InitFontReader; (* Assign font-dependent routines to various procedure variables according to information present in fontdir and dummyfont: - The last character in dummyfont defines the font format (PXL or PK). All font files are assumed to be in the same format. Note that the Options module has prefixed dummyfont with fontdir. - The last two characters in fontdir define the structure of each file spec. If ".]" then all font files are assumed to reside in subdirectories of fontdir, and the name of each subdirectory is the font size. A typical dummyfont value would be TEX_DISK:[TEX.PXL.][1500]CMR10.PXL. This is the storage scheme used in K&S's old VMS TeX distributions. If not ".]" then all font files are assumed to be in kept in fontdir, and the font size is included in the file type. A typical dummyfont value would be TEX_DISK:[TEX.PK]CMR10.300PK. This type of scheme is used in the latest VMS TeX distributions. - The dummyfont must contain a font size substring representing an unmagnified font. Its value, along with /RESOLUTION, is used to decide how to calculate the font sizes in all other font files. *) VAR i, fontsizelen, (* length of n...n in dummyfont *) dummyfontsize : CARDINAL; (* value of n...n in dummyfont *) BEGIN hexdigs := "0123456789ABCDEF"; (* for LoadBitmap *) dummyfontlen := LEN(dummyfont); IF dummyfontlen = 0 THEN dummyfontlen := 1 END; (* last char will be NULL *) CASE Cap(dummyfont[dummyfontlen-1]) OF (* last char defines format *) 'L' : formatstr := 'pxl'; formatlen := 3; FillPixelTable := PXLFillPixelTable; LoadBitmap := PXLLoadBitmap; | 'K' : formatstr := 'pk'; formatlen := 2; FillPixelTable := PKFillPixelTable; LoadBitmap := PKLoadBitmap; gpower[0] := {}; FOR i := 1 TO 8 DO gpower[i] := gpower[i-1] + {i-1}; (* used in PKLoadBitmap *) END; ELSE WriteString('/DUMMY_FONT value should end with PXL or PK.'); WriteLn; Halt(2); END; psprefixlen := LEN(psprefix); fontdirlen := LEN(fontdir); IF (fontdirlen > 1) AND (fontdir[fontdirlen-2] = '.') AND (fontdir[fontdirlen-1] = ']') THEN (* assume font files are kept in subdirectories of fontdir and have fontspecs like TEX_DISK:[TEX.subdir.][n...n]CMR10.fmt *) CompleteFontSpec := OldFontSpec; i := fontdirlen + 1; (* first n after .][ *) ELSE (* assume font files are all kept in fontdir and have fontspecs like TEX_DISK:[TEX.subdir]CMR10.n...nfmt *) CompleteFontSpec := NewFontSpec; i := fontdirlen; (* first char after ] *) WHILE (i < dummyfontlen) AND (dummyfont[i] <> '.') DO INC(i); END; INC(i); (* first n after '.' *) END; fontsizelen := 0; dummyfontsize := 0; WHILE (i < dummyfontlen) AND (dummyfont[i] >= '0') AND (dummyfont[i] <= '9') DO INC(fontsizelen); dummyfontsize := dummyfontsize * 10 + (ORD(dummyfont[i]) - ORD('0')); INC(i); END; IF fontsizelen > 0 THEN (* The xfactor used to calculate fontsize in BuildFontSpec depends on the fontsize in dummyfont (assumed to be an unmagnified font). *) IF FLOAT(dummyfontsize) / FLOAT(resolution) > 1.0 THEN xfactor := FLOAT(resolution) / 200.0; (* old naming convention *) ELSE xfactor := FLOAT(resolution) / 1000.0; (* new naming convention *) END; ELSE WriteString('/DUMMY_FONT value does not contain font size!'); WriteLn; Halt(2); END; END InitFontReader; (******************************************************************************) PROCEDURE BuildFontSpec (fontptr : fontinfoptr; VAR firstn, lastn : CARDINAL); VAR f : File; i, j, next, fontsize, tempsize, tempsizelen : CARDINAL; BEGIN WITH fontptr^ DO (* first check for a PostScript font; following code will set psfont to TRUE if psprefixlen = 0 --- ALL fonts will be considered PostScript fonts *) psfont := TRUE; i := 0; LOOP IF i = psprefixlen THEN EXIT END; IF Cap(fontname[i]) <> Cap(psprefix[i]) THEN psfont := FALSE; EXIT; END; INC(i); END; IF psfont THEN BuildTFMSpec(fontptr); (* build TFM file spec *) RETURN; END; i := 0; next := fontdirlen; REPEAT fontspec[i] := fontdir[i]; (* start fontspec with fontdir *) INC(i); UNTIL (i = next) OR (i > maxfontspec); IF next >= maxfontspec THEN fontspeclen := maxfontspec; RETURN; (* fontspec truncated *) END; fontsize := TRUNC( FLOAT(mag) * (FLOAT(scaledsize) / FLOAT(designsize)) * xfactor + 0.5 ); IF fontsize = 0 THEN INC(fontsize); (* allow for subtracting 1 *) END; tempsize := fontsize; i := 1; LOOP (* Complete rest of fontspec starting at next and return the position of first digit for fontsize. We have to try fontsize +/- 1 before giving up because rounding problems can occur in the above fontsize calculation. *) j := tempsize; tempsizelen := 0; WHILE j > 0 DO INC(tempsizelen); j := j DIV 10; END; IF NOT CompleteFontSpec(fontptr, next, tempsizelen, firstn) THEN RETURN; (* fontspec truncated *) END; lastn := firstn + tempsizelen - 1; (* put tempsize into fontspec[firstn..lastn] *) FOR j := lastn TO firstn BY -1 DO fontspec[j] := CHR(ORD('0') + (tempsize MOD 10)); tempsize := tempsize DIV 10; END; IF i > 3 THEN (* original fontsize has been restored *) RETURN; (* could not open fontspec *) END; Open(f,fontspec,FALSE); (* SYSDEP: try to open for reading *) IF Done() THEN Close(f); fontexists := TRUE; (* fontspec exists *) RETURN; ELSIF i = 1 THEN tempsize := fontsize - 1; (* try fontsize - 1 *) ELSIF i = 2 THEN tempsize := fontsize + 1; (* try fontsize + 1 *) ELSE tempsize := fontsize; (* restore original fontsize *) END; INC(i); END; END; END BuildFontSpec; (******************************************************************************) PROCEDURE BuildTFMSpec (fontptr : fontinfoptr); (* Build a complete TFM file specification in fontptr^.fontspec. This will only be done once per font; fontspeclen will no longer be 0. fontptr^.fontexists becomes TRUE if the file can be opened. *) VAR f : File; i, next : CARDINAL; BEGIN WITH fontptr^ DO i := 0; IF fontarealen > 0 THEN next := fontarealen; REPEAT fontspec[i] := fontarea[i]; (* start fontspec with fontarea *) INC(i); UNTIL (i = next) OR (i > maxfontspec); ELSE next := LEN(tfmdir); (* assume > 0 *) REPEAT fontspec[i] := tfmdir[i]; (* start fontspec with tfmdir *) INC(i); UNTIL (i = next) OR (i > maxfontspec); END; IF next >= maxfontspec THEN fontspeclen := maxfontspec; RETURN; (* fontspec truncated *) END; (* next is current length of fontspec; append fontname.tfm *) i := 0; WHILE (i < fontnamelen) AND (next < maxfontspec) DO fontspec[next] := fontname[i]; (* append fontname *) INC(i); INC(next); END; IF next + 4 <= maxfontspec THEN (* append .tfm *) fontspec[next] := '.'; INC(next); fontspec[next] := 't'; INC(next); fontspec[next] := 'f'; INC(next); fontspec[next] := 'm'; INC(next); ELSE fontspeclen := maxfontspec; RETURN; (* fontspec truncated *) END; fontspeclen := next; (* SYSDEP: terminate fontspec with NULL *) IF fontspeclen < maxfontspec THEN fontspec[fontspeclen] := NULL END; Open(f,fontspec,FALSE); (* SYSDEP: try to open for reading *) IF Done() THEN Close(f); fontexists := TRUE; (* fontspec exists *) END; END; END BuildTFMSpec; (******************************************************************************) PROCEDURE OldFontSpec (fontptr : fontinfoptr; next : CARDINAL; fontsizelen : CARDINAL; VAR firstn : CARDINAL) : BOOLEAN; (* Return TRUE if we can append "[n...n]fontname.fmt" to fontspec. Such a scheme is used in old TeX distributions from Kellerman and Smith. *) VAR i : CARDINAL; BEGIN WITH fontptr^ DO firstn := next + 1; (* position of 1st n *) IF next + fontsizelen + 1 < maxfontspec THEN (* append [n...n] *) fontspec[next] := '['; INC(next,fontsizelen + 1); (* skip n...n *) fontspec[next] := ']'; INC(next); ELSE fontspeclen := maxfontspec; RETURN FALSE; (* fontspec truncated *) END; i := 0; WHILE (i < fontnamelen) AND (next < maxfontspec) DO fontspec[next] := fontname[i]; (* append fontname *) INC(i); INC(next); END; IF next + formatlen < maxfontspec THEN (* append .fmt *) fontspec[next] := '.'; INC(next); i := 0; REPEAT fontspec[next] := formatstr[i]; INC(i); INC(next); UNTIL i = formatlen; ELSE fontspeclen := maxfontspec; RETURN FALSE; (* fontspec truncated *) END; fontspeclen := next; (* SYSDEP: terminate fontspec with NULL *) IF fontspeclen < maxfontspec THEN fontspec[fontspeclen] := NULL END; RETURN TRUE; END; END OldFontSpec; (******************************************************************************) PROCEDURE NewFontSpec (fontptr : fontinfoptr; next : CARDINAL; fontsizelen : CARDINAL; VAR firstn : CARDINAL) : BOOLEAN; (* Return TRUE if we can append "fontname.n...nfmt" to fontspec. Such a scheme is used in the latest TeX distributions. *) VAR i : CARDINAL; BEGIN WITH fontptr^ DO i := 0; WHILE (i < fontnamelen) AND (next < maxfontspec) DO fontspec[next] := fontname[i]; (* append fontname *) INC(i); INC(next); END; firstn := next + 1; (* position of 1st n *) IF next + fontsizelen + formatlen < maxfontspec THEN (* append .n...nfmt *) fontspec[next] := '.'; INC(next,fontsizelen + 1); (* skip n...n *) i := 0; REPEAT fontspec[next] := formatstr[i]; INC(i); INC(next); UNTIL i = formatlen; ELSE fontspeclen := maxfontspec; RETURN FALSE; (* fontspec truncated *) END; fontspeclen := next; (* SYSDEP: terminate fontspec with NULL *) IF fontspeclen < maxfontspec THEN fontspec[fontspeclen] := NULL END; RETURN TRUE; END; END NewFontSpec; (******************************************************************************) PROCEDURE OpenFontFile (VAR fspec : ARRAY OF CHAR) : BOOLEAN; (* Return TRUE iff given file can be opened and mapped into virtual memory. *) BEGIN InitFab(fab); (* initialize fab *) WITH fab DO FNA := ADR(fspec); (* file specification *) FNS := BYTE(LEN(fspec)); (* 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 channel := fab.STV; (* channel on which file is open *) vas[0] := 0; vas[1] := 0; status := SYS$CRMPSC (* map file into virtual address space *) (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, 16 (* page fault cluster size *) ); IF NOT ODD(status) THEN (* DEBUG WriteString('SYS$CRMPSC failed in OpenFontFile! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) RETURN FALSE; ELSE (* The entire file is mapped into virtual memory so we can access any byte as an offset from the address in vas[0]. *) filestart := vas[0]; RETURN TRUE; END; ELSE RETURN FALSE; END; END OpenFontFile; (******************************************************************************) (* Here are the functions used to get byte/s from fontfile. *) PROCEDURE GetByte () : CARDINAL; (* Return the value (unsigned) of the byte at byteoffset in fontfile and advance byteoffset for the next GetByte. *) VAR b : CARDINAL; BEGIN b := CARDINAL(filestart^[byteoffset]); INC(byteoffset); RETURN b; END GetByte; (******************************************************************************) PROCEDURE SignedByte () : INTEGER; (* Return the next byte, possibly signed. *) VAR b : CARDINAL; BEGIN b := CARDINAL(filestart^[byteoffset]); INC(byteoffset); IF b < 128 THEN RETURN b; ELSE RETURN b - 256; END; END SignedByte; (******************************************************************************) PROCEDURE GetTwoBytes () : CARDINAL; (* Return the next 2 bytes, unsigned. *) VAR a, b : CARDINAL; BEGIN a := CARDINAL(filestart^[byteoffset]); INC(byteoffset); b := CARDINAL(filestart^[byteoffset]); INC(byteoffset); RETURN a * 256 + b; END GetTwoBytes; (******************************************************************************) PROCEDURE SignedPair () : INTEGER; (* Return the next 2 bytes, possibly signed. *) VAR a, b : CARDINAL; BEGIN a := CARDINAL(filestart^[byteoffset]); INC(byteoffset); b := CARDINAL(filestart^[byteoffset]); INC(byteoffset); IF a < 128 THEN RETURN a * 256 + b; ELSE RETURN (a - 256) * 256 + b; END; END SignedPair; (******************************************************************************) PROCEDURE GetThreeBytes () : CARDINAL; (* Return the next 3 bytes, unsigned. *) VAR a, b, c : CARDINAL; BEGIN a := CARDINAL(filestart^[byteoffset]); INC(byteoffset); b := CARDINAL(filestart^[byteoffset]); INC(byteoffset); c := CARDINAL(filestart^[byteoffset]); INC(byteoffset); RETURN (a * 256 + b) * 256 + c; END GetThreeBytes; (******************************************************************************) PROCEDURE SignedQuad () : INTEGER; (* Return the value (possibly signed) of the 4 bytes at byteoffset and advance byteoffset by 4. *) VAR overlay : RECORD CASE :BOOLEAN OF TRUE : i : INTEGER | FALSE : a,b,c,d : BYTE END; END; BEGIN WITH overlay DO (* SYSDEP: on a VAX, d is at least significant end of word *) d := filestart^[byteoffset]; INC(byteoffset); c := filestart^[byteoffset]; INC(byteoffset); b := filestart^[byteoffset]; INC(byteoffset); a := filestart^[byteoffset]; INC(byteoffset); RETURN i; END; END SignedQuad; (******************************************************************************) PROCEDURE CloseFontFile; (* Close the currently open font file. *) BEGIN status := SYS$DELTVA(ADR(vas),ADR(vas),0); IF NOT ODD(status) THEN (* DEBUG WriteString('SYS$DELTVA failed in CloseFontFile! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) END; status := SYS$DASSGN(channel); IF NOT ODD(status) THEN (* DEBUG WriteString('SYS$DASSGN failed in CloseFontFile! status='); WriteCard(status); WriteLn; Halt(2); GUBED *) END; END CloseFontFile; (******************************************************************************) (* Here are the routines for reading PXL files: *) (******************************************************************************) PROCEDURE PXLFillPixelTable; (* Fill the pixeltable for currfont^ using the font directory info in the currently open PXL file. *) VAR i, b0, b1, b2, b3 : CARDINAL; (* 4 bytes in TFM width *) BEGIN WITH currfont^ DO IF psfont AND fontexists THEN TFMFillPixelTable; (* use TFM file instead *) RETURN; END; (* to find font directory we first move to last byte in PXL file *) byteoffset := CARDINAL(ADDRESS(vas[1]) - ADDRESS(filestart)); (* skip back over any 0 bytes *) WHILE (byteoffset > 0) AND (CARDINAL(filestart^[byteoffset]) = 0) DO DEC(byteoffset); END; (* move to byte at start of last non-zero word *) WHILE byteoffset MOD 4 <> 0 DO DEC(byteoffset); END; IF SignedQuad() <> 1001 THEN WriteLn; WriteString('Bad PXL file! id word <> 1001.'); WriteLn; Halt(2); END; DEC(byteoffset,4); (* SignedQuad will have added 4 *) DEC(byteoffset,516 * 4); (* starting byte of font directory *) FOR i := 128 TO maxTeXchar DO pixelptr^[i].mapadr := 0; (* PXL files only have 128 chars *) pixelptr^[i].loaded := FALSE; END; FOR i := 0 TO 127 DO WITH pixelptr^[i] DO wd := GetTwoBytes(); ht := GetTwoBytes(); xo := SignedPair(); yo := SignedPair(); loaded := FALSE; (* bitmap not yet downloaded *) mapadr := SignedQuad(); (* word offset in PXL file *) IF (wd = 0) OR (ht = 0) THEN mapadr := 0; (* in case PXL file is incorrect *) END; b0 := GetByte(); (* should be 0 or 255 *) b1 := GetByte(); b2 := GetByte(); b3 := GetByte(); dwidth := FixToDVI(b0,b1,b2,b3); pwidth := PixelRound(dwidth); (* convert DVI units to pixels *) END; END; END; END PXLFillPixelTable; (******************************************************************************) PROCEDURE FixToDVI (b0, b1, b2, b3 : CARDINAL) : INTEGER; (* Convert the given fixword (made up of 4 bytes) into DVI units using the method recommended in DVITYPE. *) VAR alpha, beta, s : CARDINAL; temp : INTEGER; BEGIN s := currfont^.scaledsize; (* so we don't change scaledsize! *) alpha := 16 * s; beta := 16; WHILE s >= 40000000B DO (* 2^23sp = 128pt *) s := s DIV 2; beta := beta DIV 2; END; temp := (((((b3 * s) DIV 400B) + (b2 * s)) DIV 400B) + (b1 * s)) DIV beta; IF b0 > 0 THEN IF b0 = 255 THEN RETURN temp - INTEGER(alpha); ELSE WriteLn; WriteString('Bad fixword! 1st byte='); WriteCard(b0); WriteLn; Halt(2); END; ELSE RETURN temp; END; END FixToDVI; (******************************************************************************) PROCEDURE PXLLoadBitmap (fontptr : fontinfoptr; code : CARDINAL); (* Download bitmap using raster information starting at mapadr in currently open PXL file. *) VAR b, r, thisbyte, bytesperrow, usedperrow, charsperline : CARDINAL; BEGIN WITH fontptr^.pixelptr^[code] DO bytesperrow := ((wd + 31) DIV 32) * 4; (* words per row * 4 *) usedperrow := (wd + 7) DIV 8; (* not all bytes might be needed *) charsperline := 0; PutString('[<'); (* output (ht * usedperrow * 2) hex digits, starting at top row of bitmap *) byteoffset := mapadr * 4; (* mapadr = word offset *) b := 0; (* byte count for one row *) r := 0; (* row count *) LOOP INC(charsperline,2); IF charsperline >= 72 THEN Put(CR); charsperline := 0; END; thisbyte := GetByte(); (* and increment byteoffset *) Put(hexdigs[ thisbyte DIV 16 ]); Put(hexdigs[ thisbyte MOD 16 ]); INC(b); IF b = usedperrow THEN INC(r); IF r = CARDINAL(ht) THEN EXIT END; INC(byteoffset,bytesperrow - b); (* move to start of next row *) b := 0; (* reset byte count *) END; END; Put('>'); Put(CR); PutCard(usedperrow * 8); Put(' '); PutInt(ht); Put(' '); PutInt(xo); Put(' '); PutInt(yo); Put(' '); (* offset of origin from top row *) PutInt(pwidth); PutString('] '); PutCard(code); PutString(' dc'); Put(CR); END; (* WITH *) END PXLLoadBitmap; (******************************************************************************) (* Here are the routines for reading PK files: *) (******************************************************************************) PROCEDURE PKFillPixelTable; (* Fill the pixeltable for currfont^ using the font directory info in the currently open PK file. *) CONST pkid = 89; pkpost = 245; pknoop = 246; pkpre = 247; VAR i, j, flagbyte, flagpos, chcode, (* assumed to be <= 255 *) packetlen, endofpacket, b0, b1, b2, b3 : CARDINAL; (* 4 bytes in TFM width *) BEGIN WITH currfont^ DO IF psfont AND fontexists THEN TFMFillPixelTable; (* use TFM file instead *) RETURN; END; byteoffset := 0; (* move to first byte *) IF GetByte() <> pkpre THEN WriteLn; WriteString('Bad pre command in '); WriteString(fontspec); WriteLn; Halt(2); END; IF GetByte() <> pkid THEN WriteLn; WriteString('Bad id byte in '); WriteString(fontspec); WriteLn; Halt(2); END; j := GetByte(); (* length of comment *) INC(byteoffset,j + 16); (* skip rest of preamble *) FOR i := 0 TO maxTeXchar DO WITH pixelptr^[i] DO mapadr := 0; (* all chars absent initially *) loaded := FALSE; (* bitmap not yet downloaded *) END; END; LOOP flagpos := byteoffset; (* remember position of flagbyte *) flagbyte := GetByte(); IF flagbyte < 240 THEN (* read character definition *) flagbyte := flagbyte MOD 8; (* value of bottom 3 bits *) IF flagbyte < 4 THEN (* short char preamble *) packetlen := flagbyte * 256 + GetByte(); chcode := GetByte(); endofpacket := packetlen + byteoffset; WITH pixelptr^[chcode] DO b1 := GetByte(); b2 := GetByte(); b3 := GetByte(); dwidth := FixToDVI(0,b1,b2,b3); (* b0 = 0 *) pwidth := GetByte(); wd := GetByte(); ht := GetByte(); xo := SignedByte(); yo := SignedByte(); END; ELSIF flagbyte < 7 THEN (* extended short char preamble *) packetlen := (flagbyte - 4) * 65536 + GetTwoBytes(); chcode := GetByte(); endofpacket := packetlen + byteoffset; WITH pixelptr^[chcode] DO b1 := GetByte(); b2 := GetByte(); b3 := GetByte(); dwidth := FixToDVI(0,b1,b2,b3); (* b0 = 0 *) pwidth := GetTwoBytes(); wd := GetTwoBytes(); ht := GetTwoBytes(); xo := SignedPair(); yo := SignedPair(); END; ELSE (* long char preamble *) packetlen := SignedQuad(); chcode := SignedQuad(); endofpacket := packetlen + byteoffset; WITH pixelptr^[chcode] DO b0 := GetByte(); b1 := GetByte(); b2 := GetByte(); b3 := GetByte(); dwidth := FixToDVI(b0,b1,b2,b3); pwidth := SignedQuad() DIV 65536; (* dx in pixels *) INC(byteoffset,4); (* skip dy *) wd := SignedQuad(); ht := SignedQuad(); xo := SignedQuad(); yo := SignedQuad(); END; END; WITH pixelptr^[chcode] DO IF (wd = 0) OR (ht = 0) THEN mapadr := 0; (* no bitmap *) ELSE mapadr := flagpos; (* position of flagbyte *) END; END; byteoffset := endofpacket; (* skip raster info *) ELSE CASE flagbyte OF 240..243 : i := 0; FOR j := 240 TO flagbyte DO i := 256 * i + GetByte() END; INC(byteoffset,i); (* skip special parameter *) | 244 : INC(byteoffset,4); (* skip numspecial parameter *) | pknoop : (* do nothing *) | pkpost : EXIT; (* no more character definitions *) ELSE WriteLn; WriteString('Bad flag byte in '); WriteString(fontspec); WriteLn; Halt(2); END; END; END; (* LOOP; flagbyte = pkpost *) END; END PKFillPixelTable; (******************************************************************************) (* Routines to unpack raster info need some global variables: *) VAR turnon : BOOLEAN; (* is current run black? *) dynf, (* dynamic packing variable *) repeatcount, (* how many times to repeat the next row *) inputbyte, (* the current input byte *) bitweight : CARDINAL; (* for getting bits or nybbles from inputbyte *) (******************************************************************************) PROCEDURE PKLoadBitmap (fontptr : fontinfoptr; code : CARDINAL); (* Download bitmap using information from character definition at mapadr in currently open PK file. *) VAR i, j, flagbyte, bitpos, bytesperrow, rowsleft, hbit, count, rp, charsperline : CARDINAL; byte : BITSET; row : ARRAY [0..400] OF BYTE; (* SYSDEP: max glyph width = 3200 bits *) BEGIN WITH fontptr^.pixelptr^[code] DO bytesperrow := (wd + 7) DIV 8; (* bytes in one row *) byteoffset := mapadr; (* mapadr = flagbyte offset in PK file *) flagbyte := GetByte(); (* assume < 240 *) dynf := flagbyte DIV 16; turnon := (flagbyte MOD 16) >= 8; (* is 1st pixel black? *) flagbyte := flagbyte MOD 8; (* value of bottom 3 bits *) IF flagbyte < 4 THEN (* skip short char preamble *) INC(byteoffset,10); ELSIF flagbyte < 7 THEN (* skip extended short char preamble *) INC(byteoffset,16); ELSE (* skip long char preamble *) INC(byteoffset,36); END; charsperline := 0; PutString('[<'); (* start of hex string *) bitweight := 0; (* to get 1st inputbyte *) IF dynf = 14 THEN (* raster info is a string of bits in the next (wd * ht + 7) DIV 8 bytes *) FOR i := 1 TO CARDINAL(ht) DO byte := {}; (* set all bits to 0 *) bitpos := 7; (* leftmost bit *) FOR j := 1 TO CARDINAL(wd) DO IF bitweight = 0 THEN (* next 2 lines equal inputbyte := GetByte(); *) inputbyte := CARDINAL(filestart^[byteoffset]); INC(byteoffset); bitweight := 8; END; DEC(bitweight); (* 7..0 *) IF bitweight IN BITSET(inputbyte) THEN INCL(byte,bitpos); (* set bit *) END; IF bitpos > 0 THEN DEC(bitpos); (* next bit *) ELSE INC(charsperline,2); IF charsperline >= 72 THEN Put(CR); charsperline := 0; END; Put(hexdigs[ CARDINAL(byte) DIV 16 ]); (* high nybble *) Put(hexdigs[ CARDINAL(byte) MOD 16 ]); (* low nybble *) byte := {}; bitpos := 7; END; END; IF bitpos < 7 THEN INC(charsperline,2); IF charsperline >= 72 THEN Put(CR); charsperline := 0; END; Put(hexdigs[ CARDINAL(byte) DIV 16 ]); Put(hexdigs[ CARDINAL(byte) MOD 16 ]); END; END; ELSE (* raster info is encoded as run and repeat counts *) rowsleft := ht; hbit := wd; repeatcount := 0; rp := 1; bitpos := 8; byte := {}; WHILE rowsleft > 0 DO count := PackedNum(); WHILE count > 0 DO IF (count < bitpos) AND (count < hbit) THEN IF turnon THEN byte := byte + gpower[bitpos] - gpower[bitpos - count]; END; DEC(hbit,count); DEC(bitpos,count); count := 0; ELSIF (count >= hbit) AND (hbit <= bitpos) THEN IF turnon THEN byte := byte + gpower[bitpos] - gpower[bitpos - hbit]; END; row[rp] := BYTE(byte); (* end of current row, so send it repeatcount+1 times *) FOR i := 0 TO repeatcount DO FOR j := 1 TO bytesperrow DO INC(charsperline,2); IF charsperline >= 72 THEN Put(CR); charsperline := 0; END; Put(hexdigs[ CARDINAL(row[j]) DIV 16 ]); Put(hexdigs[ CARDINAL(row[j]) MOD 16 ]); END; END; DEC(rowsleft,repeatcount + 1); repeatcount := 0; rp := 1; byte := {}; bitpos := 8; DEC(count,hbit); hbit := wd; ELSE IF turnon THEN byte := byte + gpower[bitpos] END; row[rp] := BYTE(byte); INC(rp); (* we assume rp never overflows! *) byte := {}; DEC(count,bitpos); DEC(hbit,bitpos); bitpos := 8; END; END; turnon := NOT turnon; END; END; Put('>'); Put(CR); PutCard(bytesperrow * 8); Put(' '); PutInt(ht); Put(' '); PutInt(xo); Put(' '); PutInt(yo); Put(' '); (* offset of origin from top row *) PutInt(pwidth); PutString('] '); PutCard(code); PutString(' dc'); Put(CR); END; (* WITH *) END PKLoadBitmap; (******************************************************************************) PROCEDURE PackedNum () : CARDINAL; (* Return next run count using algorithm given in section 23 of PKtype. A possible side-effect is to set the global repeatcount value used to duplicate the current row. *) VAR i, j : CARDINAL; BEGIN i := GetNyb(); IF i = 0 THEN REPEAT j := GetNyb(); INC(i) UNTIL j <> 0; WHILE i > 0 DO j := j * 16 + GetNyb(); DEC(i) END; RETURN j - 15 + (13 - dynf) * 16 + dynf; ELSIF i <= dynf THEN RETURN i; ELSIF i < 14 THEN RETURN (i - dynf - 1) * 16 + GetNyb() + dynf + 1; ELSE IF i = 14 THEN repeatcount := PackedNum(); (* recursive *) ELSE repeatcount := 1; (* nybble = 15 *) END; RETURN PackedNum(); (* recursive *) END; END PackedNum; (******************************************************************************) PROCEDURE GetNyb () : CARDINAL; (* Return next nybble in PK file. *) BEGIN IF bitweight = 0 THEN (* next 2 lines equal inputbyte := GetByte(); *) inputbyte := CARDINAL(filestart^[byteoffset]); INC(byteoffset); bitweight := 16; (* for next call of GetNyb *) RETURN inputbyte DIV 16; (* high nybble *) ELSE bitweight := 0; (* for next call of GetNyb *) RETURN inputbyte MOD 16; (* low nybble *) END; END GetNyb; (******************************************************************************) (* Here are the declarations and routines for reading TFM files: *) (******************************************************************************) VAR lf, lh, bc, ec, nw, nh : INTEGER; charinfo : ARRAY [0..255] OF RECORD wdindex, htindex, dpindex : INTEGER; END; charmetrics : ARRAY [0..255] OF RECORD (* 4 bytes making up fixword *) width, height, depth : ARRAY [0..3] OF INTEGER; END; (******************************************************************************) PROCEDURE TFMFillPixelTable; (* Fill the pixeltable for currfont^ (a PostScript font) using information in the currently open TFM file. *) VAR c, dheight, pheight, ddepth, pdepth : INTEGER; BEGIN ReadTFMIntegers; (* read lf..nh *) ReadTFMCharInfo; (* fill charinfo array *) ReadTFMCharMetrics; (* fill charmetrics array *) WITH currfont^ DO FOR c := 0 TO bc - 1 DO pixelptr^[c].mapadr := 0; (* chars < bc don't exist *) END; FOR c := ec + 1 TO 255 DO pixelptr^[c].mapadr := 0; (* chars > ec don't exist *) END; FOR c := bc TO ec DO WITH pixelptr^[c] DO WITH charmetrics[c] DO dwidth := FixToDVI(width[0],width[1],width[2],width[3]); dheight := FixToDVI(height[0],height[1],height[2],height[3]); ddepth := FixToDVI(depth[0],depth[1],depth[2],depth[3]); (* convert DVI units to pixels *) pwidth := PixelRound(dwidth); pheight := PixelRound(dheight); pdepth := PixelRound(ddepth); (* Since we don't have access to bitmap info for a PostScript font we will have to use the TFM width/height/depth info to approximate wd, ht, xo, yo. *) wd := pwidth; DEC(wd,wd DIV 8); (* better approximation *) ht := pheight + pdepth; xo := 0; yo := pheight - 1; IF (wd = 0) OR (ht = 0) THEN mapadr := 0; (* char all-white or not in font *) ELSE mapadr := 1; (* anything but 0 *) END; loaded := FALSE; (* no bitmap available *) END; END; END; END; END TFMFillPixelTable; (******************************************************************************) PROCEDURE ReadTFMIntegers; (* Read the first 6 16-bit integers in the TFM file. See TFtoPL section 8. *) BEGIN byteoffset := 0; (* start reading at 1st byte in TFM file *) lf := GetTwoBytes(); lh := GetTwoBytes(); bc := GetTwoBytes(); ec := GetTwoBytes(); nw := GetTwoBytes(); nh := GetTwoBytes(); END ReadTFMIntegers; (******************************************************************************) PROCEDURE ReadTFMCharInfo; (* Read the charinfo array. See TFtoPL section 11. *) VAR c, i : INTEGER; BEGIN byteoffset := 24 + (lh * 4); (* offset of charinfo array *) FOR c := bc TO ec DO WITH charinfo[c] DO wdindex := GetByte() * 4; (* offset from start of width array *) i := GetByte(); (* 2nd byte contains htindex and dpindex *) htindex := (i DIV 16) * 4; (* offset from start of height array *) dpindex := (i MOD 16) * 4; (* offset from start of depth array *) INC(byteoffset,2); (* skip itindex and remainder bytes *) END; END; END ReadTFMCharInfo; (******************************************************************************) PROCEDURE ReadTFMCharMetrics; (* Read the charmetrics array using the indices in charinfo. *) VAR wdbase, htbase, dpbase, b, c : INTEGER; BEGIN wdbase := 24 + lh * 4 + (ec - bc + 1) * 4; (* offset of width array *) htbase := wdbase + nw * 4; (* offset of height array *) dpbase := htbase + nh * 4; (* offset of depth array *) FOR c := bc TO ec DO WITH charinfo[c] DO WITH charmetrics[c] DO byteoffset := wdbase + wdindex; FOR b := 0 TO 3 DO width[b] := GetByte() END; byteoffset := htbase + htindex; FOR b := 0 TO 3 DO height[b] := GetByte() END; byteoffset := dpbase + dpindex; FOR b := 0 TO 3 DO depth[b] := GetByte() END; END; END; END; END ReadTFMCharMetrics; (******************************************************************************) BEGIN END FontReader.