DIRECTORY
Basics USING [bytesPerWord],
BasicTime USING [GMT, nullGMT, Period],
FS USING [binaryStreamOptions, EnumerateForNames, GetInfo, Open, OpenFile, StreamBufferParms, StreamFromOpenFile],
Imager USING [ConcatT, Context, Error, MaskBitmap, MaskFill, MaskRectangle],
ImagerBackdoor USING [GetTransformation],
ImagerBox USING [BoundingBox, Box, BoxFromExtents, BoxFromRectangle, Extents, ExtentsFromBox, RectangleFromBox],
ImagerFont USING [CorrectionType, nullXChar, XChar],
ImagerPath USING [CurveToProc, LineToProc, MoveToProc, PathProc],
ImagerSample USING [Box, GetBase, ObtainScratchMap, RasterSampleMap, ReleaseScratchMap, SampleMap],
ImagerTransformation USING [ApplyPreRotate, Concat, Destroy, Factor, FactoredTransformation, Rotate, Scale2, SingularValues, Transformation, TransformRectangle, TransformVec],
ImagerTypeface USING [Creator, CreatorRep, RegisterCreator, Typeface, TypefaceClass, TypefaceClassRep, TypefaceRep],
IO USING [STREAM],
PrePressFontFormat USING [CardFromBcpl, CharacterData, CharacterIndexEntry, IntFromBcpl, IXHeader, missingCharacter, missingFilePos, missingSpline, NameIndexEntry, RasterDefn, RelFilePos, SplineCode, SplineCommand, SplineCoords, SplineData, StdIndexEntry],
Real USING [FScale],
RealConvert USING [BcplToIeee],
Rope USING [Cat, Compare, Equal, Fetch, FromProc, Flatten, Index, Match, Replace, ROPE, Run, Size, Substr, Translate, TranslatorType, UnsafeMoveChars],
RopeFile USING [FromStream],
SystemNames USING [ReleaseName],
Vector2 USING [Add, Div, VEC];
MalformedCDFont:
ERROR ~
CODE;
Assert:
PROC [truth:
BOOL] ~
INLINE {
IF
NOT truth
THEN
ERROR MalformedCDFont };
Bytes:
PROC [wordSize:
NAT]
RETURNS [
CARDINAL] ~
INLINE {
RETURN [wordSize*2]};
check: [2..2] ~ Basics.bytesPerWord;
Dragon conversion note; the construct Bytes[SIZE[type]] should be changed to work properly for 32-bit machines. We can get by with this here because the press font formats are all based on 16-bit words.
FileBytes:
PROC [fileWords:
INT]
RETURNS [
INT] ~
INLINE {
RETURN [fileWords*2]};
FileBytes is used to convert a count of 16-bit words into bytes. This does not change even if the machine's word size is other than 16;
RawFetch:
UNSAFE
PROC [base:
ROPE, byteOffset:
INT, destination:
LONG
POINTER, nBytes:
NAT] ~
UNCHECKED {
bytesMoved: INT ~ Rope.UnsafeMoveChars[block: [base: destination, startIndex: 0, count: nBytes], rope: base, start: byteOffset];
Assert[bytesMoved = nBytes];
};
streamBufferParms: FS.StreamBufferParms ← [vmPagesPerBuffer: 8, nBuffers: 1];
ropeFileBufferSize: INT ← 1024;
ropeFileBuffers:
INT ← 8;
RopeFromFile:
PROC [file:
FS.OpenFile]
RETURNS [
ROPE] ~ {
stream: IO.STREAM ~ FS.StreamFromOpenFile[openFile: file, streamOptions: FS.binaryStreamOptions, streamBufferParms: streamBufferParms];
rope: ROPE ~ RopeFile.FromStream[stream: stream, bufSize: ropeFileBufferSize, buffers: ropeFileBuffers];
RETURN [rope]
};
CDCreate:
PROC [file:
FS.OpenFile]
RETURNS [Typeface] ~ {
base: ROPE ~ RopeFromFile[file];
RETURN [TypefaceFromRopes[LIST[base]]]
};
checkForBogusResolution: BOOL ← TRUE; -- There seem to be print services fonts in circulation that have a smashed resolutionX field; if this bool is true, we do some paranoid checks and smash it to 300bpi if it smells funny.
tryForCharSet:
BOOL ←
TRUE;
-- The resolutionY field has been re-used in print services fonts to represent the character set; if this bool is true, we use this interpretation after making some reasonableness checks. As long as the resolution is 256 or greater, we can always disambiguate.
NameTable: TYPE ~ REF NameTableRep;
NameTableRep:
TYPE ~
RECORD [
SEQUENCE n:
NAT
OF
ROPE];
DecodedFamily:
TYPE ~
RECORD [
familySansCharSet: ROPE ← NIL,
hasCharSet: BOOL ← FALSE,
charSet: BYTE ← 0
];
DecodeFamily:
PROC [family:
ROPE]
RETURNS [DecodedFamily] ~ {
This procedure examines a family name for the the presence of character set information.
size: NAT ~ Rope.Size[family];
charSet: BYTE ← 0;
hasCharSet: BOOL ← FALSE;
Assert[family # NIL];
IF size >= 3
THEN {
hasCharSet ← TRUE;
FOR i:
INT
IN [size-3 .. size)
DO
c: CHAR ~ Rope.Fetch[family, i];
IF c
IN ['0..'7]
THEN {charSet ← charSet*8 + (c-'0)}
ELSE {hasCharSet ← FALSE; charSet ← 0; EXIT};
ENDLOOP;
};
RETURN [[
familySansCharSet: IF hasCharSet THEN Rope.Substr[family, 0, size-3] ELSE family,
hasCharSet: hasCharSet,
charSet: charSet
]]
};
TypefaceFromRopes:
PROC [contents:
LIST
OF
ROPE]
RETURNS [Typeface] ~ {
data: Data ~ NEW[DataRep ← []];
ix: PrePressFontFormat.IXHeader;
indexFace: BYTE;
indexFamilySansCharSet: ROPE ← NIL;
groups: LIST OF GroupData ← NIL;
ValidateFamilyAndFace:
PROC [newFace:
BYTE, newFamily:
ROPE] ~ {
IF indexFamilySansCharSet =
NIL
THEN {
first time through
indexFamilySansCharSet ← newFamily;
indexFace ← newFace;
RETURN;
};
Assert[indexFace = newFace];
Assert[Rope.Equal[newFamily, indexFamilySansCharSet, FALSE]];
};
FOR each:
LIST
OF
ROPE ← contents, each.rest
UNTIL each =
NIL
DO
base: ROPE ~ each.first;
byteOffset: INT ← 0;
nameTable: NameTable ← NIL;
maxNameCode: CARDINAL ← 0;
DO
-- read the index part to find max name code
headerBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.IXHeader]];
TRUSTED { RawFetch[base, byteOffset, @ix, headerBytes] };
SELECT ix.type
FROM
end => EXIT;
name => {
name: PrePressFontFormat.NameIndexEntry;
nameBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.NameIndexEntry]];
TRUSTED { RawFetch[base, byteOffset+headerBytes, @name, nameBytes] };
maxNameCode ← MAX[maxNameCode, name.code];
};
ENDCASE => NULL;
byteOffset ← byteOffset + FileBytes[ix.length];
ENDLOOP;
nameTable ← NEW[NameTableRep[maxNameCode+1]];
byteOffset ← 0;
DO
-- read the index part to get the name codes
headerBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.IXHeader]];
TRUSTED { RawFetch[base, byteOffset, @ix, headerBytes] };
SELECT ix.type
FROM
end => EXIT;
name => {
name: PrePressFontFormat.NameIndexEntry;
nameBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.NameIndexEntry]];
i: NAT ← 0;
p: PROC RETURNS [CHAR] ~ {RETURN [VAL[name.chars[i ← i + 1]]]};
TRUSTED { RawFetch[base, byteOffset+headerBytes, @name, nameBytes] };
nameTable[name.code] ← Rope.FromProc[len: name.chars[0], p: p];
};
ENDCASE => NULL;
byteOffset ← byteOffset + FileBytes[ix.length];
ENDLOOP;
byteOffset ← 0;
DO
-- read the index part
headerBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.IXHeader]];
TRUSTED { RawFetch[base, byteOffset, @ix, headerBytes] };
SELECT ix.type
FROM
end => EXIT;
name => NULL;
spline => {
index: PrePressFontFormat.StdIndexEntry;
sdixBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.StdIndexEntry]];
group: GroupData ~ NEW[GroupDataRep];
segmentByteIndex, segmentBytes: INT ← 0;
decodedFamily: DecodedFamily ← [];
group.representation ← spline;
group.set ← 0;
Assert[FileBytes[ix.length] = headerBytes + sdixBytes];
TRUSTED { RawFetch[base, byteOffset+headerBytes, @index, sdixBytes] };
Assert[index.bc <= index.ec];
group.base ← base;
group.bc ← index.bc;
group.ec ← index.ec;
group.dataByteOffset ← FileBytes[PrePressFontFormat.CardFromBcpl[index.segmentSA]];
group.dataByteLength ← FileBytes[PrePressFontFormat.CardFromBcpl[index.segmentLength]];
Assert[group.dataByteOffset + group.dataByteLength <= Rope.Size[base]];
group.directoryByteOffset ← group.dataByteOffset + (index.ec-index.bc+1) * Bytes[SIZE[PrePressFontFormat.SplineData]];
group.pixelToChar ← ImagerTransformation.Rotate[-index.rotation/60.0];
decodedFamily ← DecodeFamily[nameTable[index.family]];
ValidateFamilyAndFace[newFace: index.face, newFamily: decodedFamily.familySansCharSet];
group.set ← decodedFamily.charSet;
{
The following makes a flat representation for the directory portion of the rope representation, to avoid having to do IO to get at the metrics. It is strictly an optimization.
splineDataEntryBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.SplineData]];
dirEntryBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.RelFilePos]];
len: NAT ~ (group.ec-group.bc+1) * (splineDataEntryBytes+dirEntryBytes);
group.base ← Rope.Replace[base: base, start: group.dataByteOffset, len: len, with: Rope.Flatten[base: base, start: group.dataByteOffset, len: len]];
};
groups ← CONS[group, groups];
};
character => {
index: PrePressFontFormat.CharacterIndexEntry;
cixBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.CharacterIndexEntry]];
group: GroupData ~ NEW[GroupDataRep];
charUnitsPerResolutionUnit: REAL ← 0;
decodedFamily: DecodedFamily ← [];
group.representation ← alignedRaster;
group.set ← 0;
Assert[FileBytes[ix.length] = headerBytes + cixBytes];
TRUSTED { RawFetch[base, byteOffset+headerBytes, @index, cixBytes] };
IF checkForBogusResolution
THEN {
IF index.resolutionX = index.resolutionY OR index.resolutionX MOD 1500 = 0 OR (SELECT index.resolutionX FROM 3840, 2000, 2540, 2400, 720 => TRUE ENDCASE => FALSE) THEN NULL ELSE index.resolutionX ← 3000
};
IF tryForCharSet
THEN {
IF index.resolutionY
MOD 10 = 0
AND index.resolutionY/10
IN CharSet
THEN {
group.set ← index.resolutionY/10;
index.resolutionY ← index.resolutionX;
};
};
Assert[index.bc <= index.ec];
group.base ← base;
group.bc ← index.bc;
group.ec ← index.ec;
group.dataByteOffset ← FileBytes[PrePressFontFormat.CardFromBcpl[index.segmentSA]];
group.dataByteLength ← FileBytes[PrePressFontFormat.CardFromBcpl[index.segmentLength]];
Assert[group.dataByteOffset + group.dataByteLength <= Rope.Size[base]];
group.directoryByteOffset ← group.dataByteOffset + (index.ec-index.bc+1) * Bytes[SIZE[PrePressFontFormat.CharacterData]];
charUnitsPerResolutionUnit ← 25400.0/index.size; -- units of resolution are dots per 10 inches
group.pixelToChar ← ImagerTransformation.Scale2[[
charUnitsPerResolutionUnit/index.resolutionX,
charUnitsPerResolutionUnit/index.resolutionY
]];
IF index.rotation#0 THEN group.pixelToChar.ApplyPreRotate[-index.rotation/60.0];
decodedFamily ← DecodeFamily[nameTable[index.family]];
ValidateFamilyAndFace[newFace: index.face, newFamily: decodedFamily.familySansCharSet];
IF decodedFamily.hasCharSet THEN group.set ← decodedFamily.charSet;
{
The following makes a flat representation for the directory portion of the rope representation, to avoid having to do IO to get at the metrics. It is strictly an optimization.
charDataEntryBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.CharacterData]];
dirEntryBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.RelFilePos]];
len: NAT ~ (group.ec-group.bc+1) * (charDataEntryBytes+dirEntryBytes);
group.base ← Rope.Replace[base: base, start: group.dataByteOffset, len: len, with: Rope.Flatten[base: base, start: group.dataByteOffset, len: len]];
};
groups ← CONS[group, groups];
};
ENDCASE => ERROR MalformedCDFont; -- unexpected ix type
byteOffset ← byteOffset + FileBytes[ix.length];
ENDLOOP;
ENDLOOP;
Assert[indexFamilySansCharSet # NIL];
data.groups ← SortGroups[groups];
data.setTable ← BuildSetTable[data.groups];
data.amplifySpace ← indexFace < 18; -- 40B is an ordinary character in TEX fonts
RETURN[NEW[ImagerTypeface.TypefaceRep ← [class: cdClass, data: data]]];
};
InOrder:
PROC [a, b: GroupData]
RETURNS [
BOOL] ~ {
SELECT
TRUE
FROM
a.set # b.set => RETURN [a.set < b.set];
a.representation # b.representation AND (a.representation=spline OR b.representation=spline) => RETURN [a.representation < b.representation];
ENDCASE => {
sva: VEC ~ ImagerTransformation.SingularValues[a.pixelToChar];
svb: VEC ~ ImagerTransformation.SingularValues[b.pixelToChar];
IF sva.x < svb.x THEN RETURN [TRUE];
IF sva.x = svb.x AND sva.y < svb.y THEN RETURN [TRUE];
RETURN [FALSE];
};
};
SortGroups:
PROC [groups:
LIST
OF GroupData]
RETURNS [
LIST
OF GroupData] ~ {
unconsumed: LIST OF GroupData ← groups;
new: LIST OF GroupData ← NIL;
WHILE unconsumed #
NIL
DO
rest: LIST OF GroupData ~ unconsumed.rest;
current: GroupData ~ unconsumed.first;
a: LIST OF GroupData ← new;
p: LIST OF GroupData ← NIL;
WHILE a#NIL AND NOT InOrder[a.first, current] DO p ← a; a ← a.rest ENDLOOP;
IF p =
NIL
THEN { unconsumed.rest ← new; new ← unconsumed }
ELSE { unconsumed.rest ← p.rest; p.rest ← unconsumed };
unconsumed ← rest;
ENDLOOP;
RETURN [new];
};
BuildSetTable:
PROC [groups:
LIST
OF GroupData]
RETURNS [SetTable] ~ {
setTable: SetTable ~ NEW[SetTableRep ← ALL[NIL]];
setbc: REF PACKED ARRAY CharSet OF BYTE ← NEW[PACKED ARRAY CharSet OF BYTE ← ALL[LAST[BYTE]]];
setec: REF PACKED ARRAY CharSet OF BYTE ← NEW[PACKED ARRAY CharSet OF BYTE ← ALL[FIRST[BYTE]]];
FOR each:
LIST
OF GroupData ← groups, each.rest
UNTIL each =
NIL
DO
group: GroupData ~ each.first;
set: BYTE ~ group.set;
setbc^[set] ← MIN[group.bc, setbc^[set]];
setec^[set] ← MAX[group.ec, setec^[set]];
ENDLOOP;
FOR set: CharSet
IN CharSet
DO
IF setbc[set] <= setec[set]
THEN {
charTable: CharTable ~ NEW[CharTableRep[setec[set]-setbc[set]+1]];
charTable.bc ← setbc^[set];
charTable.ec ← setec^[set];
FOR i: NAT IN [0..charTable.size) DO charTable[i] ← NIL ENDLOOP;
setTable[set] ← charTable;
};
ENDLOOP;
FOR each:
LIST
OF GroupData ← groups, each.rest
UNTIL each =
NIL
DO
group: GroupData ~ each.first;
charTable: CharTable ~ setTable[group.set];
FOR code:
BYTE
IN [group.bc..group.ec]
DO
SELECT group.representation
FROM
spline => {
sd: PrePressFontFormat.SplineData ~ GetSplineData[group, code];
IF sd.wx#PrePressFontFormat.missingSpline
THEN {
wx: REAL ~ RealConvert.BcplToIeee[sd.wx];
wy: REAL ~ RealConvert.BcplToIeee[sd.wy];
e: VEC ~ ImagerTransformation.TransformVec[group.pixelToChar, [wx, wy]];
wbb: ImagerBox.Box ~ [xmin: RealConvert.BcplToIeee[sd.xmin], ymin: RealConvert.BcplToIeee[sd.ymin], xmax: RealConvert.BcplToIeee[sd.xmax], ymax: RealConvert.BcplToIeee[sd.ymax]];
box: ImagerBox.Box ~ TransformBox[group.pixelToChar, wbb];
charMetrics: CharMetrics ~ charTable[code-charTable.bc];
IF charMetrics =
NIL
THEN charTable[code-charTable.bc] ← NEW [CharMetricsRep ← [escapement: e, bb: box]]
ELSE charMetrics.bb ← ImagerBox.BoundingBox[charMetrics.bb, box];
};
};
alignedRaster => {
cd: PrePressFontFormat.CharacterData ~ GetCharacterData[group, code];
IF cd.bbdy#PrePressFontFormat.missingCharacter
THEN {
wx: REAL ~ Real.FScale[PrePressFontFormat.IntFromBcpl[cd.wx], -16];
wy: REAL ~ Real.FScale[PrePressFontFormat.IntFromBcpl[cd.wy], -16];
e: VEC ~ ImagerTransformation.TransformVec[group.pixelToChar, [wx, wy]];
box: ImagerBox.Box ~ ImagerBox.BoxFromRectangle[ImagerTransformation.TransformRectangle[group.pixelToChar, [x: cd.bbox, y: cd.bboy, w: cd.bbdx, h: cd.bbdy]]];
charMetrics: CharMetrics ~ charTable[code-charTable.bc];
IF charMetrics =
NIL
THEN charTable[code-charTable.bc] ← NEW [CharMetricsRep ← [escapement: e, bb: box]]
ELSE charMetrics.bb ← ImagerBox.BoundingBox[charMetrics.bb, box];
};
};
ENDCASE => ERROR;
ENDLOOP;
ENDLOOP;
setbc ← NIL; setec ← NIL; -- Local use only; an explicit FREE here would work
RETURN [setTable]
};
TransformBox:
PROC [m: Transformation, box: ImagerBox.Box]
RETURNS [ImagerBox.Box] ~ {
RETURN [ImagerBox.BoxFromRectangle[ImagerTransformation.TransformRectangle[m, ImagerBox.RectangleFromBox[box]]]]
};
GetCharacterData:
PROC [group: GroupData, code:
BYTE]
RETURNS [PrePressFontFormat.CharacterData] ~ {
characterData: PrePressFontFormat.CharacterData;
cdBytes: INT ~ Bytes[SIZE[PrePressFontFormat.CharacterData]];
IF group.representation # alignedRaster THEN ERROR;
characterData.bbdy ← PrePressFontFormat.missingCharacter;
IF code
IN [group.bc..group.ec]
THEN TRUSTED { RawFetch[group.base, group.dataByteOffset + (code-group.bc) * cdBytes, @characterData, cdBytes] };
RETURN [characterData];
};
GetSplineData:
PROC [group: GroupData, code:
BYTE]
RETURNS [PrePressFontFormat.SplineData] ~ {
splineData: PrePressFontFormat.SplineData;
splineDataBytes: INT ~ Bytes[SIZE[PrePressFontFormat.SplineData]];
IF group.representation # spline THEN ERROR;
splineData.wx ← PrePressFontFormat.missingSpline;
IF code
IN [group.bc..group.ec]
THEN TRUSTED { RawFetch[group.base, group.dataByteOffset + (code-group.bc) * splineDataBytes, @splineData, splineDataBytes] };
RETURN [splineData];
};
CDContains:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [
BOOL] ~ {
data: Data ~ NARROW[self.data];
charTable: CharTable ~ data.setTable[char.set];
IF charTable = NIL OR char.code NOT IN [charTable.bc..charTable.ec] THEN RETURN [FALSE];
RETURN [charTable[char.code-charTable.bc] # NIL];
};
CDNextChar:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [ImagerFont.XChar] ~ {
data: Data ~ NARROW[self.data];
next: XChar ← IF char = nullXChar THEN [0, 0] ELSE IF char.code = LAST[BYTE] THEN [set: char.set+1, code: FIRST[BYTE]] ELSE [set: char.set, code: char.code+1];
charTable: CharTable ← data.setTable[next.set];
UNTIL next = nullXChar
OR (charTable #
NIL
AND next.code
IN [charTable.bc..charTable.ec]
AND charTable[next.code-charTable.bc] #
NIL)
DO
SELECT
TRUE
FROM
charTable =
NIL
OR next.code > charTable.ec
OR next.code =
LAST[
BYTE] => {
next ← IF next.set = nullXChar.set THEN nullXChar ELSE [next.set+1, 0];
charTable ← data.setTable[next.set];
};
next.code < charTable.bc => next.code ← charTable.bc;
ENDCASE => next.code ← next.code + 1;
ENDLOOP;
RETURN [next];
};
CDEscapement:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [
VEC] ~ {
data: Data ~ NARROW[self.data];
charTable: CharTable ~ data.setTable[char.set];
IF charTable #
NIL
AND char.code
IN [charTable.bc..charTable.ec]
THEN {
charMetrics: CharMetrics ~ charTable[char.code-charTable.bc];
IF charMetrics # NIL THEN RETURN [charMetrics.escapement]
};
RETURN[[0.5, 0]];
};
CDAmplified:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [
BOOL] ~ {
data: Data ~ NARROW[self.data];
RETURN [data.amplifySpace AND char = [set: 0, code: 40B]];
};
CDCorrection:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [ImagerFont.CorrectionType] ~ {
data: Data ~ NARROW[self.data];
IF CDContains[self, char]
THEN {
IF data.amplifySpace AND char = [set: 0, code: 40B] THEN RETURN[space];
RETURN[mask];
};
RETURN[none];
};
CDBoundingBox:
PROC [self: Typeface, char: ImagerFont.XChar]
RETURNS [Extents] ~ {
data: Data ~ NARROW[self.data];
charTable: CharTable ~ data.setTable[char.set];
IF charTable #
NIL
AND char.code
IN [charTable.bc..charTable.ec]
THEN {
charMetrics: CharMetrics ~ charTable[char.code-charTable.bc];
IF charMetrics # NIL THEN RETURN [ImagerBox.ExtentsFromBox[charMetrics.bb]];
};
IF char # substituteChar THEN RETURN [CDBoundingBox[self, substituteChar]];
RETURN[[leftExtent: -0.05, rightExtent: 0.45, descent: 0, ascent: 0.6]];
};
CDFontBoundingBox:
PROC [self: Typeface]
RETURNS [Extents] ~ {
data: Data ~ NARROW[self.data];
setTable: SetTable ~ data.setTable;
bb: ImagerBox.Box ← ImagerBox.BoxFromExtents[CDBoundingBox[self, substituteChar]];
FOR set: CharSet
IN CharSet
DO
charTable: CharTable ~ setTable[set];
IF charTable #
NIL
THEN {
FOR code:
BYTE
IN [charTable.bc..charTable.ec]
DO
charMetrics: CharMetrics ~ charTable[code-charTable.bc];
IF charMetrics #
NIL
THEN {
b: ImagerBox.Box ~ charMetrics.bb;
bb ← [xmin: MIN[bb.xmin, b.xmin], ymin: MIN[bb.ymin, b.ymin], xmax: MAX[bb.xmax, b.xmax], ymax: MAX[bb.ymax, b.ymax]]
};
ENDLOOP;
};
ENDLOOP;
RETURN [ImagerBox.ExtentsFromBox[bb]]
};
CDKern: PROC [self: Typeface, char, successor: ImagerFont.XChar] RETURNS [VEC] ~ { RETURN[[0, 0]] };
CDNextKern: PROC [self: Typeface, char, successor: ImagerFont.XChar] RETURNS [ImagerFont.XChar] ~ { RETURN[ImagerFont.nullXChar] };
CDLigature: PROC [self: Typeface, char, successor: ImagerFont.XChar] RETURNS [ImagerFont.XChar] ~ { RETURN[ImagerFont.nullXChar] };
CDNextLigature: PROC [self: Typeface, char, successor: ImagerFont.XChar] RETURNS [ImagerFont.XChar] ~ { RETURN[ImagerFont.nullXChar] };
GetBitmap:
PROC [group: GroupData, code:
BYTE]
RETURNS [ImagerSample.RasterSampleMap] ~ {
sampleMap: ImagerSample.RasterSampleMap ← NIL;
cd: PrePressFontFormat.CharacterData ~ GetCharacterData[group, code];
IF cd.bbdy#PrePressFontFormat.missingCharacter
THEN
TRUSTED {
rfpBytes: INT ~ Bytes[SIZE[PrePressFontFormat.RelFilePos]];
rfpBytePos: INT ~ group.directoryByteOffset+(code-group.bc)*rfpBytes;
rfp: PrePressFontFormat.RelFilePos;
TRUSTED {RawFetch[group.base, rfpBytePos, @rfp, rfpBytes] };
IF rfp # PrePressFontFormat.missingFilePos
THEN {
relativeByte: INT ~ FileBytes[PrePressFontFormat.IntFromBcpl[rfp]];
rdBytes: INT ~ Bytes[SIZE[PrePressFontFormat.RasterDefn]];
rd: PrePressFontFormat.RasterDefn;
RawFetch[group.base, group.directoryByteOffset+relativeByte, @rd, rdBytes];
Assert[rd.lines=cd.bbdx AND rd.raster=(cd.bbdy+15)/16];
IF cd.bbdx>0
AND cd.bbdy>0
THEN {
rasterBytes: INT ~ FileBytes[LONG[rd.raster]*rd.lines];
sampleMap ← ImagerSample.ObtainScratchMap[
box: [min: [s: cd.bbox, f: cd.bboy], max: [s: cd.bbdx+cd.bbox, f: cd.bbdy+cd.bboy]],
bitsPerLine: raster*16, -- this is really 16, not bitsPerWord!
bitsPerSample: 1
];
TRUSTED {RawFetch[group.base, group.directoryByteOffset+relativeByte+rdBytes, ImagerSample.GetBase[sampleMap].word, rasterBytes] };
};
};
};
RETURN [sampleMap];
};
Right:
PROC [angle:
REAL]
RETURNS [
BOOL] ~ {
WHILE angle < 0 DO angle ← angle + 90.0 ENDLOOP;
WHILE angle > 45.0 DO angle ← angle - 90.0 ENDLOOP;
RETURN [ABS[angle] <= 1.666667E-2]
};
minScale: REAL ← 0.9875;
maxScale: REAL ← 1.0125;
FindBestGroup:
PROC [data: Data, char: ImagerFont.XChar, t: Transformation]
RETURNS [GroupData] ~ {
t may be NIL, in which case we only try for splines.
best: GroupData ← NIL;
FOR each:
LIST
OF GroupData ← data.groups, each.rest
UNTIL each =
NIL
DO
group: GroupData ~ each.first;
IF group.set = char.set
THEN {
SELECT group.representation
FROM
spline => {best ← group};
alignedRaster => {
cd: PrePressFontFormat.CharacterData ~ GetCharacterData[group, char.code];
IF cd.bbdy#PrePressFontFormat.missingCharacter
THEN {
IF t #
NIL
THEN {
composite: Transformation ← ImagerTransformation.Concat[group.pixelToChar, t];
f: ImagerTransformation.FactoredTransformation ~ ImagerTransformation.Factor[composite];
ImagerTransformation.Destroy[composite]; composite ← NIL;
IF Right[f.r1] AND Right[f.r2] AND ABS[f.s.x] IN [minScale..maxScale] AND ABS[f.s.y] IN [minScale..maxScale] THEN {best ← group; EXIT};
};
IF best = NIL THEN best ← group;
};
};
ENDCASE => ERROR;
};
ENDLOOP;
IF best = NIL THEN ERROR; -- CDContains lied!
RETURN [best];
};
GetClientToDevice:
PROC [context: Imager.Context]
RETURNS [t: Transformation ←
NIL] ~ {
returns NIL if the context does not have a client-to-device transformation
t ← ImagerBackdoor.GetTransformation[context: context, from: client, to: device ! Imager.Error => CONTINUE];
};
CDMask:
PROC [self: Typeface, char: ImagerFont.XChar, context: Imager.Context] ~ {
data: Data ~ NARROW[self.data];
IF CDContains[self, char]
THEN {
t: Transformation ← GetClientToDevice[context];
group: GroupData ~ FindBestGroup[data, char, t];
IF t # NIL THEN { ImagerTransformation.Destroy[t]; t ← NIL};
SELECT group.representation
FROM
spline => MaskSpline[group, char.code, context];
alignedRaster => {
bitmap: ImagerSample.SampleMap ← GetBitmap[group, char.code];
IF bitmap #
NIL
THEN {
Imager.ConcatT[context, group.pixelToChar];
Imager.MaskBitmap[context: context, bitmap: bitmap, referencePoint: [0, 0], scanMode: [slow: right, fast: up], position: [0, 0]];
ImagerSample.ReleaseScratchMap[bitmap];
};
};
ENDCASE => ERROR;
}
ELSE {
IF char # substituteChar
THEN CDMask[self, substituteChar, context]
ELSE Imager.MaskRectangle[context, [0.05, 0, 0.4, 0.6]];
};
};
MaskSpline:
PROC [group: GroupData, code:
BYTE, context: Imager.Context] ~ {
path: ImagerPath.PathProc ~ { MapSplineOutline[group: group, code: code, moveTo: moveTo, lineTo: lineTo, curveTo: curveTo] };
Imager.MaskFill[context: context, path: path, oddWrap: TRUE];
};
MapSplineOutline:
PROC [group: GroupData, code:
BYTE, moveTo: ImagerPath.MoveToProc, lineTo: ImagerPath.LineToProc, curveTo: ImagerPath.CurveToProc] ~ {
InitByteIndex:
PROC
RETURNS [
INT] ~
TRUSTED {
filePos: PrePressFontFormat.RelFilePos;
filePosBytes: INT ~ Bytes[SIZE[PrePressFontFormat.RelFilePos]];
RawFetch[base: group.base, byteOffset: group.directoryByteOffset + (code-group.bc)*filePosBytes, destination: @filePos, nBytes: filePosBytes];
IF filePos=PrePressFontFormat.missingFilePos THEN ERROR MalformedCDFont;
RETURN [group.directoryByteOffset + FileBytes[PrePressFontFormat.IntFromBcpl[filePos]]];
};
initByteIndex: INT ~ InitByteIndex[];
byteIndex: INT ← initByteIndex;
lp: VEC ← [0, 0];
GetCode:
PROC
RETURNS [PrePressFontFormat.SplineCode] ~
TRUSTED {
sCmd: PrePressFontFormat.SplineCommand;
nBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.SplineCommand]];
RawFetch[base: group.base, byteOffset: byteIndex, destination: @sCmd, nBytes: nBytes];
byteIndex ← byteIndex + nBytes;
RETURN[sCmd.code];
};
GetCoords:
PROC
RETURNS [
VEC] ~
TRUSTED {
sCo: PrePressFontFormat.SplineCoords;
nBytes: NAT ~ Bytes[SIZE[PrePressFontFormat.SplineCoords]];
RawFetch[base: group.base, byteOffset: byteIndex, destination: @sCo, nBytes: nBytes];
byteIndex ← byteIndex + nBytes;
RETURN[[RealConvert.BcplToIeee[sCo.x], RealConvert.BcplToIeee[sCo.y]]];
};
DO
SELECT GetCode[]
FROM
$moveTo => {
p: VEC ~ GetCoords[];
moveTo[p];
lp ← p;
};
$drawTo => {
p: VEC ~ GetCoords[];
lineTo[p];
lp ← p;
};
$drawCurve => {
c1: VEC ~ GetCoords[];
c2: VEC ~ GetCoords[];
c3: VEC ~ GetCoords[];
b1: VEC ~ lp.Add[c1.Div[3]];
b2: VEC ~ b1.Add[c1.Add[c2].Div[3]];
b3: VEC ~ lp.Add[c1].Add[c2].Add[c3];
curveTo[b1, b2, b3];
lp ← b3;
};
$endDefinition => EXIT;
$newObject => ERROR MalformedCDFont; -- not implemented
ENDCASE => ERROR MalformedCDFont; -- undefined
ENDLOOP;
nSplineChars ← nSplineChars + 1;
totalSplineBytes ← totalSplineBytes + (byteIndex-initByteIndex);
maxSplineBytes ← MAX[maxSplineBytes, (byteIndex-initByteIndex)];
};
nSplineChars: INT ← 0;
totalSplineBytes: INT ← 0;
cdClass: ImagerTypeface.TypefaceClass ~
NEW [ImagerTypeface.TypefaceClassRep ← [
type: $CD,
Contains: CDContains,
NextChar: CDNextChar,
Escapement: CDEscapement,
Amplified: CDAmplified,
Correction: CDCorrection,
BoundingBox: CDBoundingBox,
FontBoundingBox: CDFontBoundingBox,
Ligature: CDLigature,
NextLigature: CDNextLigature,
Kern: CDKern,
NextKern: CDNextKern,
Mask: CDMask
]];
releaseName: ROPE ~ SystemNames.ReleaseName[];
versionKet:
ROPE ← Rope.Cat[releaseName, ">"];
PrefixSizeFromFileName:
PROC [fullFName:
ROPE]
RETURNS [
INT] ~ {
d: INT ← 0;
Strip:
PROC [rope:
ROPE]
RETURNS [
BOOL] ~ {
size: INT ~ Rope.Size[rope];
IF Rope.Run[s1: fullFName, pos1: d, s2: rope, case:
FALSE] = size
THEN {
d ← d + size; RETURN [TRUE]
};
RETURN [FALSE]
};
IF NOT Strip["[]<>"] THEN ERROR;
WHILE Strip["Fonts>"] OR Strip[versionKet] DO ENDLOOP;
RETURN [d];
};
CSVersionFromFileName:
PROC [fullFName:
ROPE]
RETURNS [
ROPE] ~ {
d1: INT ~ PrefixSizeFromFileName[fullFName]; -- Skip file name prefix
d2: INT ~ Rope.Index[fullFName, d1, ">"]+1; -- Skip "Xerox>"
d3: INT ~ Rope.Index[fullFName, d2, ">"]; -- Find end of version part
RETURN [Rope.Substr[fullFName, d2, d3-d2]];
};
FontNameFromFileName:
PROC [fullFName:
ROPE]
RETURNS [
ROPE] ~ {
d1: INT ~ PrefixSizeFromFileName[fullFName]; -- Skip file name prefix
d2: INT ~ Rope.Index[fullFName, d1+1, "."]; -- Find end of font name
translator: Rope.TranslatorType ~ { new ← IF old = '> THEN '/ ELSE old };
rope: ROPE ~ Rope.Translate[base: fullFName, start: d1, len: d2-d1, translator: translator];
RETURN [rope]
};
xcFontRootSlashes:
ROPE ← Rope.Cat["///", releaseName, "/Fonts/Xerox/"];
for example, "///7.0/Fonts/Xerox/"
XCCreate:
PROC [self: ImagerTypeface.Creator, name:
ROPE, substitute:
BOOL]
RETURNS [Typeface] ~ {
IF Rope.Match["xerox/xc*/*", name,
FALSE]
THEN {
vStart: INT ~ Rope.Index[name, 0, "/"]+1;
vEnd: INT ~ Rope.Index[name, vStart, "/"];
charSetVersion: ROPE ~ Rope.Substr[name, vStart, vEnd-vStart];
shortName: ROPE ~ Rope.Substr[name, vEnd+1];
versionPattern: ROPE ~ IF substitute THEN "xc*" ELSE charSetVersion;
pattern: ROPE ~ Rope.Cat[xcFontRootSlashes, versionPattern, "/", shortName, ".cd*!H"];
matches: LIST OF ROPE ← NIL;
matchedVersion: ROPE ← NIL;
nameProc:
PROC [fullFName:
ROPE]
RETURNS [continue:
BOOL ←
TRUE] ~ {
csVersion: ROPE ~ CSVersionFromFileName[fullFName];
IF
NOT Rope.Equal[csVersion, matchedVersion,
FALSE]
THEN {
IF Rope.Compare[matchedVersion, charSetVersion, FALSE] IN [equal..greater]
THEN RETURN [continue: FALSE];
matchedVersion ← csVersion;
matches ← NIL;
};
matches ← CONS[fullFName, matches];
};
FS.EnumerateForNames[pattern: pattern, proc: nameProc];
IF matches #
NIL
THEN {
contents: LIST OF ROPE ← NIL;
typeface: Typeface ← NIL;
newestCreated: BasicTime.GMT ← BasicTime.nullGMT;
FOR each:
LIST
OF
ROPE ← matches, each.rest
UNTIL each =
NIL
DO
file: FS.OpenFile ~ FS.Open[each.first];
created: BasicTime.GMT ~ FS.GetInfo[file].created;
base: ROPE ~ RopeFromFile[file];
contents ← CONS[base, contents];
IF newestCreated = BasicTime.nullGMT OR BasicTime.Period[from: created, to: newestCreated] < 0 THEN newestCreated ← created;
ENDLOOP;
typeface ← TypefaceFromRopes[contents];
typeface.name ← FontNameFromFileName[matches.first];
typeface.created ← newestCreated;
RETURN [typeface]
};
};
RETURN [NIL]
};
PressFontCreator:
PROC [self: ImagerTypeface.Creator, name:
ROPE, substitute:
BOOL]
RETURNS [Typeface] ~ {
IF Rope.Match["xerox/pressfonts/*", name,
FALSE]
THEN {
pattern: ROPE ~ Rope.Cat["///", releaseName, "/Fonts/", name, ".cd*!H"];
matches: LIST OF ROPE ← NIL;
nameProc:
PROC [fullFName:
ROPE]
RETURNS [continue:
BOOL ←
TRUE] ~ {
matches ← CONS[fullFName, matches];
};
FS.EnumerateForNames[pattern: pattern, proc: nameProc];
IF matches #
NIL
THEN {
contents: LIST OF ROPE ← NIL;
typeface: Typeface ← NIL;
newestCreated: BasicTime.GMT ← BasicTime.nullGMT;
FOR each:
LIST
OF
ROPE ← matches, each.rest
UNTIL each =
NIL
DO
file: FS.OpenFile ~ FS.Open[each.first];
created: BasicTime.GMT ~ FS.GetInfo[file].created;
base: ROPE ~ RopeFromFile[file];
contents ← CONS[base, contents];
IF newestCreated = BasicTime.nullGMT OR BasicTime.Period[from: created, to: newestCreated] < 0 THEN newestCreated ← created;
ENDLOOP;
typeface ← TypefaceFromRopes[contents];
typeface.name ← FontNameFromFileName[matches.first];
typeface.created ← newestCreated;
RETURN [typeface]
};
};
RETURN [NIL]
};
DiagnosticFontCreator:
PROC [self: ImagerTypeface.Creator, name:
ROPE, substitute:
BOOL]
RETURNS [Typeface] ~ {
IF Rope.Match["xerox/diagnostic/*", name,
FALSE]
THEN {
pattern: ROPE ~ Rope.Cat["///", releaseName, "/Fonts/", name, ".cd*!H"];
matches: LIST OF ROPE ← NIL;
nameProc:
PROC [fullFName:
ROPE]
RETURNS [continue:
BOOL ←
TRUE] ~ {
matches ← CONS[fullFName, matches];
};
FS.EnumerateForNames[pattern: pattern, proc: nameProc];
IF matches #
NIL
THEN {
contents: LIST OF ROPE ← NIL;
typeface: Typeface ← NIL;
newestCreated: BasicTime.GMT ← BasicTime.nullGMT;
FOR each:
LIST
OF
ROPE ← matches, each.rest
UNTIL each =
NIL
DO
file: FS.OpenFile ~ FS.Open[each.first];
created: BasicTime.GMT ~ FS.GetInfo[file].created;
base: ROPE ~ RopeFromFile[file];
contents ← CONS[base, contents];
IF newestCreated = BasicTime.nullGMT OR BasicTime.Period[from: created, to: newestCreated] < 0 THEN newestCreated ← created;
ENDLOOP;
typeface ← TypefaceFromRopes[contents];
typeface.name ← FontNameFromFileName[matches.first];
typeface.created ← newestCreated;
RETURN [typeface]
};
};
RETURN [NIL]
};
xcCreator: ImagerTypeface.Creator ~
NEW[ImagerTypeface.CreatorRep ← [proc: XCCreate, data:
NIL]];
pressFontCreator: ImagerTypeface.Creator ~
NEW[ImagerTypeface.CreatorRep ← [proc: PressFontCreator, data:
NIL]];
diagnosticFontCreator: ImagerTypeface.Creator ~ NEW[ImagerTypeface.CreatorRep ← [proc: DiagnosticFontCreator, data: NIL]];
ImagerTypeface.RegisterCreator[xcCreator, TRUE];
ImagerTypeface.RegisterCreator[pressFontCreator,
TRUE];
ImagerTypeface.RegisterCreator[ImagerTypeface.CreatorFromFileExtension["AC", CDCreate]];
ImagerTypeface.RegisterCreator[ImagerTypeface.CreatorFromFileExtension["CD", CDCreate]];
ImagerTypeface.RegisterCreator[ImagerTypeface.CreatorFromFileExtension["SD", CDCreate]];