-- texpack.mesa

-- Tex routines for packing lists into boxes
-- last written by Doug Wyatt, January 19, 1980  9:40 PM

DIRECTORY
	TexDefs: FROM "TexDefs",
	TexErrorDefs: FROM "TexErrorDefs",
	TexFontDefs: FROM "TexFontDefs",
	TexGlueDefs: FROM "TexGlueDefs",
	TexNodeDefs: FROM "TexNodeDefs",
	TexPackDefs: FROM "TexPackDefs",
	TexTableDefs: FROM "TexTableDefs",
	TexTokenDefs: FROM "TexTokenDefs";

TexPack: PROGRAM
IMPORTS TexErrorDefs,TexFontDefs,TexGlueDefs,TexNodeDefs,
	TexTableDefs,TexTokenDefs
EXPORTS TexPackDefs =
BEGIN OPEN TexGlueDefs,TexDefs,TexNodeDefs;

OverfullBox: PUBLIC SIGNAL[box: BoxNodePtr, excess: Dimn] = CODE;

packstrings: BOOLEAN=TRUE;

-- total stretch,shrink of each order found by packaging routine
privateflexsums: FlexSums;
packflexsums: PUBLIC FlexSumsPtr←@privateflexsums;

HPackage: PUBLIC PROCEDURE
	[list: NodeListPtr, desiredwidth: Dimn, xpand: BOOLEAN,
	inserts: NodeListPtr, flexsums: FlexSumsPtr]
	RETURNS[BoxNodePtr] =
	BEGIN
	-- This procedure runs through the hlist headed by list and
	-- returns a pointer to a box formed from it. The width of the box is
	-- 	desiredwidth, if xpand = FALSE
	-- 	natural width + desiredwidth, if xpand = TRUE (expansion).
	-- One consequence is that the box has its natural width if xpand = TRUE
	-- and desiredwidth = 0. The box may actually extend outside its computed
	-- dimensions if the desired width is less than the natural width minus the
	-- maximum amount of shrinkage. list's listhead is destroyed.

	-- The variable inserts points to a list which receives all topinserts
	-- or botinserts or ejects that are affixed to this hlist, and they are
	-- removed from the hlist.

	-- The variable flexsums points to a FlexSums array where the total
	-- stretch and shrink of the glue is stored.

	p,prevp: NodePtr; -- current and previous node
	b: BoxNodePtr; -- the resulting box node
	ht,dp,wd: Dimn; -- computed height, depth, width
	delta: Dimn; -- difference of actual width from desired width

	DoWHD: PROCEDURE[w,h,d: Dimn] = INLINE
		BEGIN wd←wd+w; ht←MAX[ht, h]; dp←MAX[dp, d] END;
	DoChar: PROCEDURE[c: FChar] = INLINE
		BEGIN OPEN TexFontDefs;
		DoWHD[w: CharWd[c], h: CharHt[c], d: CharDp[c]];
		END;
	DoBox: PROCEDURE[b: BoxNodePtr] = INLINE
		BEGIN
		DoWHD[w: b.width, h: b.height-b.shiftamt, d: b.depth+b.shiftamt];
		END;

	prevp←list; -- beginning of given hlist
	ht←dp←wd←0; -- computed height and depth will be >=0
	ClearFlexSums[flexsums]; -- all stretches and shrinks initially zero

	WHILE (p←prevp.link)#NIL
		DO
		WITH pp:p SELECT FROM
			char => DoChar[pp.c];
			box => DoBox[@pp];
			unset => DoBox[pp.box];
			rule => DoWHD[w: pp.width, h: pp.height, d: pp.depth];
			space,kern => wd←wd+pp.s;
			glue => BEGIN wd←wd+pp.g.space; SumFlex[pp.g, flexsums] END;
			leader,hyph,penalty,disc => NULL;
			eject,ins =>
				BEGIN
				prevp.link←p.link; p.link←NIL;
				StoreNode[inserts, p];
				LOOP; -- don't change prevp
				END;
			ENDCASE => ERROR TexErrorDefs.Confusion; -- bad Node type
		prevp←p;
		ENDLOOP;

	-- Now the statistics-gathering and node-shuffling is complete,
	-- so we wrap it up

	-- *** try compacting runs of char nodes into string nodes
	IF packstrings THEN CompactStrings[list];

	IF xpand THEN desiredwidth←wd+desiredwidth;
	b←MakeBoxNode[dir: hlist, head: FinishNodeList[list],
		h: ht, d: dp, w: desiredwidth];
	-- *** do something about b.contains
	IF (delta←desiredwidth-wd)#0 THEN
		BEGIN
		b.glueset←SetGlue[dir: IF delta>0 THEN str ELSE shr,
			delta: ABS[delta], sums: flexsums !Overfull =>
				BEGIN SIGNAL OverfullBox[b,excess]; RESUME END];
		IF b.glueset=zeroGlueSet THEN b.altered←TRUE;
		END
	ELSE b.glueset←zeroGlueSet;
	RETURN[b];
	END;

CompactStrings: PROCEDURE[list: NodeListPtr] =
	BEGIN
	str: STRING←[maxstringlength];
	prevp,p: NodePtr;
	prevp←list;
	UNTIL (p←prevp.link)=NIL
		DO
		WITH pp:p SELECT FROM
			char =>
				BEGIN
				n: CARDINAL←1;
				prevq,q: NodePtr;
				f: Font←pp.c.font;
				str[0]←pp.c.char;
				prevq←p;
				WHILE (q←prevq.link)#NIL AND n<maxstringlength
					DO
					WITH qq:q SELECT FROM
						char =>
							BEGIN
							IF qq.c.font#f THEN EXIT;
							str[n]←qq.c.char; n←n+1;
							END;
						disc => NULL;
						ENDCASE => EXIT;
					prevq.link←q.link; DsNode[q];
					ENDLOOP;
				IF n>1 THEN
					BEGIN
					DsNode[p]; str.length←n; p←MakeStringNode[f,str];
					prevp.link←p; p.link←q;
					END;
				END;
			ENDCASE;
		prevp←prevp.link;
		ENDLOOP;
	END;


-- pack an hlist with desired width dw
HPack: PUBLIC PROCEDURE[list: NodeListPtr, dw: Dimn, xp: BOOLEAN]
	RETURNS[BoxNodePtr] =
	BEGIN
	inserts: NodeListPtr←InitNodeList[];
	b: BoxNodePtr←HPackage[list: list, desiredwidth: dw, xpand: xp,
		inserts: inserts, flexsums: packflexsums];
	FreeNodeList[inserts]; -- inserts are forgotten
	RETURN[b];
	END;

-- pack an hlist with its natural width
HBox: PUBLIC PROCEDURE[list: NodeListPtr] RETURNS[BoxNodePtr] =
	BEGIN
	RETURN[HPack[list, 0, TRUE]];
	END;


VPackage: PUBLIC PROCEDURE
	[list: NodeListPtr, desiredheight: Dimn, xpand: BOOLEAN,
	page: BOOLEAN, flexsums: FlexSumsPtr←packflexsums]
	RETURNS[BoxNodePtr] =
	BEGIN
	-- This procedure runs through the vlist pointed to by list.link and
	-- returns a pointer to a box formed from it. The height of the box is
	-- 	desiredheight, if xpand = FALSE
	-- 	natural height + desiredheight, if xpand = TRUE (expansion).
	-- One consequence is that the box has its natural height if xpand=TRUE
	-- and desiredheight = 0. The box may actually extend outside its computed
	-- dimensions if the desired height is less than the natural height minus
	-- the maximum amount of shrinkage, or if boxes have been shifted left of
	-- the reference point.

	-- All topinserts are replaced by the corresponding vlist, which is moved
	-- to the front of the list. Similarly, all botinserts move to the bottom
	-- (relative order being otherwise preserved). Any mark nodes encountered
	-- will change the value of "botmark". The global variables str,shr are
	-- set to the total stretch and shrink of the glue.

	-- If "page" is true, the depth of the resulting box is constrained to be
	-- at most pagedepthmax.

	-- Note: list.last need not be valid.

	toplist: NodeListPtr←InitNodeList[]; -- list for topinserts
	botlist: NodeListPtr←InitNodeList[]; -- list for botinserts
	ht,dp,wd: Dimn←0; -- the box dimensions so far
	delta: Dimn;
	b: BoxNodePtr; -- the resulting box node

	VScan: PROCEDURE[list: NodeListPtr, insertsOK: BOOLEAN] =
		BEGIN
		-- This procedure runs through a vlist, accumulating its overall
		-- height, depth, width, stretch, and shrink
		-- list.last is set to point to the last node in the list
		p,prevp: NodePtr; -- current node and previous node
		DoWHD: PROCEDURE[w,h,d: Dimn] = --INLINE--
			BEGIN wd←MAX[w,wd]; ht←ht+dp+h; dp←d END;
		DoChar: PROCEDURE[c: FChar] = INLINE
			BEGIN OPEN TexFontDefs;
			DoWHD[w: CharWd[c], h: CharHt[c], d: CharDp[c]];
			END;
		DoBox: PROCEDURE[b: BoxNodePtr] = --INLINE--
			BEGIN DoWHD[w: b.width+b.shiftamt, h: b.height, d: b.depth] END;

		prevp←list;
		WHILE (p←prevp.link)#NIL
			DO
			WITH pp:p SELECT FROM
				char => DoChar[pp.c];
				box => DoBox[@pp];
				unset => DoBox[pp.box];
				rule => DoWHD[w: pp.width, h: pp.height, d: pp.depth];
				glue => BEGIN ht←ht+dp+pp.g.space; dp←0; SumFlex[pp.g, flexsums] END;
				-- ***** allow kern Nodes in vlists??
				space,kern => BEGIN ht←ht+dp+pp.s; dp←0 END;
				leader,penalty,eject => NULL;
				mark => SetMark[pp.t];
				ins =>
					BEGIN
					inslist: NodeListPtr←MakeNodeList[pp.vlist];
					pp.vlist←NIL; -- don't clobber the list when we delete ins node
					IF NOT insertsOK THEN
						ERROR TexErrorDefs.Confusion; -- no inserts permitted
					-- now scan the list to be inserted
					VScan[inslist, FALSE--there are no inserts in inserts--];
					SELECT pp.where FROM
						top => AppendNodeList[toplist, inslist];
						bot => AppendNodeList[botlist, inslist];
						ENDCASE => ERROR;
					prevp.link←p.link; DsNode[p]; -- remove ins Node and its glue
					LOOP; -- don't change prevp
					END;
				ENDCASE => ERROR TexErrorDefs.Confusion; -- bad Node type
			prevp←prevp.link;
			ENDLOOP;
		list.last←prevp; -- point to last node in list
		END;

	-- the code for VPackage starts here

	ClearFlexSums[flexsums];

	VScan[list, TRUE]; -- scan the vlist, allowing insertions

	-- now link in the inserts
	InsertNodeList[list, toplist];
	AppendNodeList[list, botlist];

	-- Now the statistics-gathering and node-shuffling pass is complete,
	-- so we wrap it up
	IF page THEN
		BEGIN
		maxdp: Dimn=TexTableDefs.DimnParam[maxdepth];
		IF dp>maxdp THEN BEGIN ht←ht+dp-maxdp; dp←maxdp END;
		END;
	IF xpand THEN desiredheight←ht+desiredheight;
	b←MakeBoxNode[dir: vlist, head: FinishNodeList[list],
		h: desiredheight, d: dp, w: wd];
	IF (delta←desiredheight-ht)#0 THEN
		BEGIN
		b.glueset←SetGlue[dir: IF delta>0 THEN str ELSE shr,
			delta: ABS[delta], sums: flexsums !Overfull =>
				BEGIN SIGNAL OverfullBox[b,excess]; RESUME END];
		IF b.glueset=zeroGlueSet THEN b.altered←TRUE;
		END
	ELSE b.glueset←zeroGlueSet;
	RETURN[b];
	END;

-- pack a vlist with desired height dh
VPack: PUBLIC PROCEDURE[list: NodeListPtr, dh: Dimn, xp: BOOLEAN←FALSE]
	RETURNS[BoxNodePtr] =
	BEGIN
	RETURN[VPackage[list: list, desiredheight: dh, xpand: xp,
		page: FALSE, flexsums: packflexsums]];
	END;

-- pack a vlist with its natural height
VBox: PUBLIC PROCEDURE[list: NodeListPtr] RETURNS[BoxNodePtr] =
	BEGIN
	RETURN[VPack[list, 0, TRUE]];
	END;

TokenListPtr: TYPE = TexTokenDefs.TokenListPtr;

mark: TokenListPtr←NIL;

CurMark: PUBLIC PROCEDURE RETURNS[TokenListPtr] =
	BEGIN RETURN[mark] END;

SetMark: PROCEDURE[t: TokenListPtr] =
	BEGIN OPEN TexTokenDefs;
	IF mark#NIL THEN DelRCLink[mark];
	AddRCLink[mark←t];
	END;

END.