-- TexMathB.mesa -- Tex routines for dealing with math mode -- last written by Doug Wyatt, December 5, 1979 2:23 AM DIRECTORY TexDefs: FROM "TexDefs", TexErrorDefs: FROM "TexErrorDefs", TexFontDefs: FROM "TexFontDefs", TexGlueDefs: FROM "TexGlueDefs", TexMathDefs: FROM "TexMathDefs", TexMathOpDefs: FROM "TexMathOpDefs", TexMemDefs: FROM "TexMemDefs", TexNoadDefs: FROM "TexNoadDefs", TexNodeDefs: FROM "TexNodeDefs", TexPackDefs: FROM "TexPackDefs", TexTableDefs: FROM "TexTableDefs"; TexMathB: PROGRAM IMPORTS TexErrorDefs,TexFontDefs,TexGlueDefs,TexMathOpDefs,TexMemDefs, TexNoadDefs,TexNodeDefs,TexPackDefs,TexTableDefs EXPORTS TexMathOpDefs = BEGIN OPEN TexNodeDefs,TexNoadDefs,TexDefs,TexMathOpDefs,TexMathDefs; -- **************************** -- Major math mode procedures -- **************************** -- these global variables are maintained by MlistToHlist as it -- runs through an mlist curstyle: MathStyle; -- the style used at noad q cursize: MathSize; -- FontSize[curstyle], the type size used at noad q drt: Dimn; -- the default rule thickness penalties: BOOLEAN; maxh,maxd: Dimn; -- the maximum height,depth of the mlist -- the table that governs inter-element mlist spacing SpaceArray: TYPE = ARRAY MType OF ARRAY MType OF MathSpace; spaceArray: POINTER TO SpaceArray_NIL; MathBInit: PROCEDURE = BEGIN spaceArray_TexMemDefs.AllocMem[SIZE[SpaceArray]]; spaceArray^_ [ [ no, thin, op, thick, no, no, no], -- Ord [ thin, thin, nil, thick, no, no, no], -- Op [ op, op, nil, nil, op, nil, nil], -- Bin [thick, thick, nil, no, thick, no, no], -- Rel [ no, no, nil, no, no, no, no], -- Open [ no, thin, op, thick, no, no, no], -- Close [ th, th, nil, thick, th, th, th] -- Punct ]; -- Ord, Op, Bin, Rel, Open, Close, Punct END; SpaceTable: PROCEDURE[a,b: MType] RETURNS[MathSpace] = --INLINE-- BEGIN RETURN[spaceArray[a][b]] END; MCharToFChar: PROCEDURE[mc: MChar, size: MathSize] RETURNS[FChar] = --INLINE-- BEGIN RETURN[[font: MathFontTable[size, mc.mfont], char: mc.char]]; END; WrongMFieldType: SIGNAL = CODE; -- this asserts that the given MField contains a box -- after debugging, it could be replaced by a LOOPHOLE BoxF: PROCEDURE[f: MFieldPtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN WITH ff:f SELECT FROM box => RETURN[ff.box]; ENDCASE => ERROR WrongMFieldType; END; -- this is used for vtop TopHeight: PROCEDURE[p: NodePtr] RETURNS[Dimn] = --INLINE-- BEGIN WHILE p#NIL DO WITH pp:p SELECT FROM char => RETURN[TexFontDefs.CharHt[pp.c]]; box => RETURN[pp.height]; rule => RETURN[pp.height]; glue => EXIT; ENDCASE; -- continue looping p_p.link; ENDLOOP; RETURN[0]; END; SetStyle: PROCEDURE[s: MathStyle] = --INLINE-- BEGIN cursize_FontSize[curstyle_s] END; DispStyle: PROCEDURE RETURNS[BOOLEAN] = --INLINE-- BEGIN RETURN[curstyle.style=disp] END; DoVctr: PROCEDURE[r: BoxNodePtr, vctr: VctrType] = --INLINE-- BEGIN SELECT vctr FROM vcenter => r.shiftamt_(r.height-r.depth)/2-MathPar[axisheight,cursize]; vtop => r.shiftamt_r.height-TopHeight[r.head]; ENDCASE => ERROR; -- invalid VctrType END; OpKern: PROCEDURE[b: BoxNodePtr] RETURNS[kern: Dimn] = --INLINE-- BEGIN p: CharNodePtr; -- now set kern nonzero if the operator in box b is a single -- character in the mathex font, having a nonzero MathKern IF (p_SingleCharBox[b])#NIL THEN BEGIN ch: FChar_p.c; -- ch is the character in the char Node IF ch.font=MathFontTable[text,ex] THEN RETURN[TexFontDefs.CharIc[ch]]; -- ch is in the mathex font END; RETURN[0]; END; CancelBin: PROCEDURE[r: CommonNoadPtr] = --INLINE-- BEGIN IF r#NIL AND r.mtype=Bin THEN r.mtype_Ord; END; NotBinContext: PROCEDURE[r: CommonNoadPtr] RETURNS[BOOLEAN] = --INLINE-- BEGIN RETURN[r=NIL OR (SELECT r.mtype FROM Bin,Op,Rel,Open,Punct => TRUE, ENDCASE => FALSE)]; END; DoSqrt: PROCEDURE[b: BoxNodePtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN radical: Delimiter=[small:[TRUE,[sy,160C]],large:[TRUE,[ex,160C]]]; r: BoxNodePtr; -- box containing the radical symbol clr: Dimn; -- extra blank space above operand list: NodeListPtr_InitNodeList[]; b_CleanBox[b]; IF DispStyle[] THEN clr_MathFontPar[xheight,cursize]/4+drt ELSE clr_(5*drt)/4; r_VarSymbol[radical, curstyle, b.height+b.depth+clr+drt]; -- Now r points to a box containing a radical sign of sufficient -- size. The upper left corner of the corresponding rule should -- touch the upper right corner of this box. We still need to -- raise or lower the box appropriately. r.shiftamt_(r.height-r.depth-b.height+b.depth-clr-drt)/2; -- Now top of box minus drt = b.height+clr plus half the excess r.link_OverBar[b, r.height-r.shiftamt, drt, (IF penalties THEN drt ELSE 2*drt)]; StoreNode[list,r]; RETURN[TexPackDefs.HBox[list]]; END; DoOver: PROCEDURE[b: BoxNodePtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN b_CleanBox[b]; RETURN[OverBar[b, b.height+3*drt, drt, (IF penalties THEN drt ELSE 2*drt)]]; END; DoUnder: PROCEDURE[b: BoxNodePtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN list: NodeListPtr_InitNodeList[]; StoreNode[list,b_CleanBox[b]]; -- first the operand StoreNode[list,MakeSpace[2*drt]]; -- then some glue StoreNode[list,FractionRule[drt]]; -- finally, the underbar RETURN[MakeBoxNode[dir: vlist, head: FinishNodeList[list], h: b.height, d: b.depth+(IF penalties THEN 4 ELSE 5)*drt, w: b.width]]; END; DoAccent: PROCEDURE[b: BoxNodePtr, accent: MChar] RETURNS[BoxNodePtr] = --INLINE-- BEGIN -- Slants are not taken into account in mathmode accents, since -- the sizes of math characters are already adjusted for slant p: BoxNodePtr; g: GlueNodePtr; h,t: Dimn; list: NodeListPtr_InitNodeList[]; p_BoxChar[accent, curstyle, FALSE].box; -- the accent char, in proper size b_CleanBox[b]; g_MakeGlueNode[TexGlueDefs.CommonGlue[lowerfill]]; -- make a vlist StoreNode[list,p]; -- the accent StoreNode[list,g]; -- some lowerfill glue StoreNode[list,b]; -- the accentee p.shiftamt_(b.width-p.width)/2; -- center the accent h_b.height; t_MathFontPar[xheight,cursize]; -- we will raise the accent by h-t p.width_0; -- the accent won't count in determining the new width RETURN[TexPackDefs.VPack[list, p.height+h-t]]; END; DoOpLimits: PROCEDURE[middle,upper,lower: BoxNodePtr, kern: Dimn] RETURNS[BoxNodePtr] = --INLINE-- BEGIN shiftup,shiftdown,maxw,h,d,extra: Dimn; list: NodeListPtr_InitNodeList[]; IF upper=NIL AND lower=NIL THEN RETURN[middle]; -- no limits to do IF middle=NIL THEN middle_NullBox[]; -- limits are to be centered above and below the operator -- (except modified by kern, the upper limit being shifted -- right and the lower limit shifted left by kern/2 each) IF upper#NIL THEN BEGIN upper_CleanBox[upper]; shiftup_MAX[MathExPar[bigopspacing3]-upper.depth, MathExPar[bigopspacing1]]; END ELSE BEGIN upper_NullBox[]; shiftup_0 END; IF lower#NIL THEN BEGIN lower_CleanBox[lower]; shiftdown_MAX[MathExPar[bigopspacing4]-lower.height, MathExPar[bigopspacing2]]; END ELSE BEGIN lower_NullBox[]; shiftdown_0 END; maxw_MAX[middle.width-kern, lower.width, upper.width]; upper_ReBox[upper,maxw,kern]; middle_ReBox[CleanBox[middle],maxw,kern/2]; lower_ReBox[lower,maxw,0]; extra_MathExPar[bigopspacing5]; -- extra space above and below limits h_middle.height-middle.shiftamt+upper.depth+upper.height; IF shiftup#0 THEN h_h+shiftup+extra; d_middle.depth+middle.shiftamt+lower.height+lower.depth; IF shiftdown#0 THEN d_d+shiftdown+extra; IF shiftup=0 THEN StoreNode[list,upper] ELSE BEGIN StoreNode[list,MakeSpace[extra]]; StoreNode[list,upper]; StoreNode[list,MakeSpace[shiftup]]; END; StoreNode[list,middle]; IF shiftdown=0 THEN StoreNode[list,lower] ELSE BEGIN StoreNode[list,MakeSpace[shiftdown]]; StoreNode[list,lower]; StoreNode[list,MakeSpace[extra]]; END; RETURN[MakeBoxNode[dir: vlist, head: FinishNodeList[list], h: h, d: d, w: maxw+kern]]; END; SupTable: PROCEDURE[s: MathStyle] RETURNS[MathParType] = --INLINE-- BEGIN RETURN[IF s.variant=atop THEN sup3 ELSE (IF s.style=disp THEN sup1 ELSE sup2)] END; DoScripts: PROCEDURE[b,bsup,bsub: BoxNodePtr, kern: Dimn, op: BOOLEAN] RETURNS[BoxNodePtr] = --INLINE-- BEGIN -- Process the sub/superscripts of noad q d: BoxNodePtr; shiftup,shiftdown: Dimn_0; IF bsup=NIL AND bsub=NIL THEN RETURN[b]; -- no super or subscript IF b#NIL AND (op OR SingleCharBox[b]=NIL OR b.shiftamt#0) THEN BEGIN -- the operand is not simply a character siz: MathSize_FontSize[ScrStyle[curstyle]]; shiftup_MAX[0, b.height-b.shiftamt-MathPar[supdrop,siz]]; shiftdown_MAX[0, b.depth+b.shiftamt+MathPar[subdrop,siz]]; END; -- shiftup and shiftdown are minimum amounts to shift baselines IF bsup=NIL THEN BEGIN -- subscript but no superscript d_CleanBox[bsub]; shiftdown_MAX[shiftdown, MathPar[sub1,cursize]]; -- make sure that the subscript doesn't get above the baseline -- plus four-fifths the xheight shiftdown_MAX[shiftdown, d.height-(4*MathFontPar[xheight,cursize])/5]; d.shiftamt_shiftdown; IF kern#0 THEN BEGIN list: NodeListPtr_InitNodeList[]; StoreNode[list,MakeSpace[-kern]]; StoreNode[list,d]; d_TexPackDefs.HBox[list]; END; END ELSE BEGIN -- superscript present shiftup_MAX[shiftup, MathPar[SupTable[curstyle],cursize]]; d_CleanBox[bsup]; -- make sure that the exponent doesn't get below the basline plus -- one-fourth the xheight shiftup_MAX[shiftup, MathFontPar[xheight,cursize]/4+d.depth]; IF bsub=NIL THEN d.shiftamt_-shiftup -- superscript but no subscript ELSE BEGIN -- both subscript and superscript c: BoxNodePtr_CleanBox[bsub]; delta: Dimn; list: NodeListPtr_InitNodeList[]; shiftdown_MAX[shiftdown, MathPar[sub2,cursize]]; delta_(d.depth+c.height+drt)-(shiftup+shiftdown); IF delta>0 THEN BEGIN -- adjust scripts to ensure minimum clearance drt shiftup_shiftup+delta/2; shiftdown_shiftdown+delta/2; END; StoreNode[list,d]; StoreNode[list,MakeGlueNode[TexGlueDefs.CommonGlue[fill]]]; StoreNode[list,c]; c.shiftamt_-kern; -- kern might be nonzero if np.ctype=op d_TexPackDefs.VPack[list, shiftdown+shiftup+d.height]; d.shiftamt_shiftdown; END; END; -- Now d points to a box representing the sub/superscripts -- and b is the box to attach it to IF b=NIL THEN RETURN[d] ELSE BEGIN list: NodeListPtr_InitNodeList[]; StoreNode[list,b]; StoreNode[list,d]; RETURN[TexPackDefs.HBox[list]]; END; END; DoAbove: PROCEDURE[np: AboveNoadPtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN num: BoxNodePtr_CleanBox[BoxF[@np.numerator]]; denom: BoxNodePtr_CleanBox[BoxF[@np.denominator]]; rt: Dimn_np.aboverule; -- rule thickness axis: Dimn_MathPar[axisheight,cursize]; pn,pd: MathParType; shiftup,shiftdown,maxw,s: Dimn; r: BoxNodePtr; ld,rd: BoxNodePtr; -- left and right delimiters dispstyle: BOOLEAN_DispStyle[]; list: NodeListPtr_InitNodeList[]; IF dispstyle THEN BEGIN pn_num1; pd_denom1 END ELSE BEGIN pn_IF rt=0 THEN num3 ELSE num2; pd_denom2 END; shiftup_MathPar[pn,cursize]; shiftdown_MathPar[pd,cursize]; -- Now axis is the distance from the base line to the center of the -- bar line, while shiftup and shiftdown are the standard baseline -- displacements for numerator and denominator in the current style. -- These standard displacements will be increased, if necessary, to -- avoid interference between numerator and denominator. -- Center the numerator and denominator by reboxing the smaller one maxw_MAX[num.width,denom.width]; IF num.width0 THEN BEGIN shiftup_shiftup+delta/2; shiftdown_shiftdown+delta/2 END; END ELSE BEGIN -- the case of a fraction line -- clr is the min clearance desired between num, denom, and rule clr: Dimn_IF dispstyle THEN 3*rt ELSE rt; delta1,delta2: Dimn; -- possible additions to shiftup, shiftdown delta1_(num.depth+clr+rt/2)-(shiftup-axis); delta2_(denom.height+clr+rt/2)-(shiftdown+axis); SELECT TRUE FROM (delta1>0 AND delta2>0) => -- both get minimum clearance BEGIN shiftup_shiftup+delta1; shiftdown_shiftdown+delta2 END; -- otherwise, both get clearance of the good one (delta1>0) => shiftup_shiftup+delta1-delta2; (delta2>0) => shiftdown_shiftdown+delta2-delta1; ENDCASE; END; -- make the vlist box for the fraction StoreNode[list,num]; -- first comes the numerator IF rt=0 THEN BEGIN -- no rule inserted h: Dimn_shiftup+shiftdown-num.depth-denom.height; StoreNode[list,MakeSpace[h]]; -- glue inbetween num and denom END ELSE BEGIN h1: Dimn_shiftup-num.depth-rt/2-axis; h2: Dimn_shiftdown+axis-denom.height-rt/2; StoreNode[list,MakeSpace[h1]]; -- glue above fraction bar StoreNode[list,FractionRule[rt]]; -- the fraction bar StoreNode[list,MakeSpace[h2]]; -- glue below fraction bar END; StoreNode[list,denom]; -- last comes the denominator r_MakeBoxNode[dir: vlist, head: FinishNodeList[list], h: num.height+shiftup, d: denom.depth+shiftdown, w: maxw]; -- Finally, put the fraction into a box with its delimiters s_MathPar[(IF dispstyle THEN delim1 ELSE delim2),cursize]; ld_VarSymbol[np.ldelim, curstyle, s]; rd_VarSymbol[np.rdelim, curstyle, s]; ld.shiftamt_(ld.height-ld.depth)/2-axis; rd.shiftamt_(rd.height-rd.depth)/2-axis; list_InitNodeList[]; -- ldelim, fraction, rdelim StoreNode[list,ld]; StoreNode[list,r]; StoreNode[list,rd]; RETURN[TexPackDefs.HBox[list]]; END; -- This procedure does most of the mathematics formatting: It converts -- an mlist to an hlist, provided that the noads of the mlist contain no -- references to other mlists. (The procedure "evalmlist" below makes it -- possible to assume that this condition is satisfied.) If "penalties" -- is true, penalty nodes that indicate permissible breaks in the main -- mlist will be inserted MlistToHlist: PUBLIC PROCEDURE[p: NoadPtr, style: MathStyle, penlt: BOOLEAN] RETURNS[NodePtr] = BEGIN mlist: NoadListPtr_InitNoadList[]; -- the mlist being scanned hlist: NodeListPtr_InitNodeList[]; -- the hlist being formed -- We make two passes over the mlist. On the first pass, boxes are -- constructed for square roots and fractions, etc., and -- sub/superscripts are attached. A few other minor operations are -- also done (e.g., binnoads are changed to boxnoads if they don't -- appear in the context of binary operators, and the height and depth -- are calculated so that left and right delimiters of the appropriate -- size will be fabricated. The second pass gets rid of all noads, -- and hooks together the desired hlist including appropriate -- glue and penalty nodes IF p=NIL THEN RETURN[NIL]; -- avoid degenerate case mlist.link_p; drt_MathExPar[defaultrulethickness]; penalties_penlt; maxh_maxd_0; ScanMlist[mlist,style]; MakeHlist[mlist,hlist,style]; RETURN[FinishNodeList[hlist]]; END; -- the first pass of MlistToHlist ScanMlist: PROCEDURE[mlist: NoadListPtr, style: MathStyle] = --INLINE-- BEGIN q: NoadPtr_mlist; -- runs through the mlist prevq: NoadPtr_NIL; -- the noad preceding q (prevq.link=q) r: CommonNoadPtr_NIL; -- the previous CommonNoad -- On this first pass, boxes are constructed for square roots and -- fractions, etc., and sub/superscripts are attached. A few other -- minor operations are also done (e.g., binnoads are changed to -- boxnoads if they don't appear in the context of binary operators, -- and the height and depth are calculated so that left and right -- delimiters of the appropriate size will be fabricated. SetStyle[style]; FOR prevq_mlist,q UNTIL (q_prevq.link)=NIL DO -- the first pass WITH qq:q SELECT FROM common => BEGIN b,sup,sub: BoxNodePtr; WITH qqq:qq SELECT FROM scripted => BEGIN kern: Dimn_0; opflag,oplimits: BOOLEAN_FALSE; SELECT qq.mtype FROM Rel,Close,Punct => CancelBin[r]; Bin => IF NotBinContext[r] THEN qq.mtype_Ord; ENDCASE; b_BoxF[@qqq.operand]; WITH qqqq:qqq SELECT FROM none => NULL; vctr => DoVctr[b,qqqq.vctr]; op => BEGIN opflag_TRUE; kern_OpKern[b]; oplimits_kern=0; IF qqqq.limitswitch THEN oplimits_NOT oplimits; END; sqrt => b_DoSqrt[b]; over => b_DoOver[b]; under => b_DoUnder[b]; accent => b_DoAccent[b,qqqq.accent]; ENDCASE => ERROR; -- bad NType -- attach sub/superscripts if present sup_BoxF[@qqq.supscr]; sub_BoxF[@qqq.subscr]; IF oplimits AND DispStyle[] THEN b_DoOpLimits[b,sup,sub,kern] ELSE b_DoScripts[b,sup,sub,kern,opflag]; END; above => b_DoAbove[@qqq]; delim => b_NIL; ENDCASE; IF b#NIL THEN BEGIN qq.box_b; maxh_MAX[maxh, b.height-b.shiftamt]; maxd_MAX[maxd, b.depth+b.shiftamt]; END; r_@qq; END; node,disc => NULL; style => SetStyle[qq.s]; space => BEGIN -- substitute for this space Noad a node Noad for g -- g is a pointer to a glue node or NIL g: NodePtr_MakeMathGlue[qq.sp, cursize]; n: NoadPtr_MakeNodeNoad[g]; n.link_qq.link; prevq.link_q_n; END; ENDCASE => ERROR; -- invalid noad type ENDLOOP; -- end of first pass loop END; -- The second pass of MlistToHlist MakeHlist: PROCEDURE[mlist: NoadListPtr, hlist: NodeListPtr, style: MathStyle] = BEGIN q: NoadPtr; -- runs through the mlist nextq: NoadPtr; -- holds q.link while q is freed rtype,t: MType; -- previous and current node types, for spacing binpen: Penalty_TexTableDefs.CurPenalty[mbpen]; -- penalty for break at Bin relpen: Penalty_TexTableDefs.CurPenalty[mrpen]; -- penalty for break at Rel pen: Penalty; -- penalty for breaking after q break: BOOLEAN; -- TRUE if a break is allowed and pen has been set Appnd: PROCEDURE[x: NodePtr] = --INLINE-- BEGIN IF x#NIL THEN StoreNode[hlist,x] END; -- The second pass simply goes through and inserts the appropriate -- spacing, returning the noads to free storage. It also handles -- leftnoads and rightnoads, since we now know maxh and maxd rtype_Open; SetStyle[style]; FOR q_mlist.link,nextq WHILE q#NIL DO -- second pass loop break_FALSE; WITH qq:q SELECT FROM common => BEGIN WITH qqq:qq SELECT FROM scripted,above => NULL; delim => BEGIN axis: Dimn_MathPar[axisheight,FontSize[style]]; s: Dimn_MAX[maxh-axis,maxd+axis]; -- max distance from axis b: BoxNodePtr_VarSymbol[qqq.delim, curstyle, 2*s]; b.shiftamt_(b.height-b.depth)/2-axis; qq.box_b; END; ENDCASE => ERROR; -- bad CommonNoad type SELECT (t_qq.mtype) FROM Bin => BEGIN pen_binpen; break_TRUE END; Rel => BEGIN pen_relpen; break_TRUE END; ENDCASE; Appnd[InterElementGlue[rtype,t,cursize]]; Appnd[qq.box]; IF break AND penalties AND NOT PenaltyNodeFollows[@qq] THEN Appnd[MakePenaltyNode[pen]]; rtype_t; END; node => Appnd[qq.p]; disc => Appnd[MakeDiscNode[MCharToFChar[qq.c, cursize]]]; style => SetStyle[qq.s]; ENDCASE => ERROR; -- invalid Noad type nextq_q.link; ENDLOOP; END; EvalMlist: PUBLIC PROCEDURE[p: NoadPtr, style: MathStyle, penalties: BOOLEAN] RETURNS[NodePtr] = BEGIN -- This procedure converts the general mlist pointed to by p into -- an hlist, using the given style for the main mlist. The effect is -- like MlistToHlist except that the given mlist may have sub-mlists, or it -- might refer to math characters that aren't already in boxes. This is the -- procedure that controls the implicit styles in math formulas. Recursion -- occurs when evalmlist calls boxfield which calls evalmlist q: NoadPtr; curstyle: MathStyle_style; FOR q_p,q.link WHILE q#NIL DO WITH qq:q SELECT FROM -- we must remove non-box fields from noad q common => WITH qqq:qq SELECT FROM scripted => BEGIN scrstyle: MathStyle_ScrStyle[curstyle]; SELECT qqq.stype FROM sqrt,over => BoxField[@qqq.operand, UndStyle[curstyle], TRUE]; op => BoxOp[@qqq.operand,curstyle]; ENDCASE => BoxField[@qqq.operand, curstyle, ~KernScript[@qqq]]; -- The last parameter to BoxField essentially makes a "kerned" -- symbol when there is a subscript but no superscript. -- Otherwise the italic correction is included as the box is made BoxField[@qqq.supscr,scrstyle,TRUE]; BoxField[@qqq.subscr,UndStyle[scrstyle],TRUE]; END; above => BEGIN BoxField[@qqq.numerator,NumStyle[curstyle],TRUE]; BoxField[@qqq.denominator,DenomStyle[curstyle],TRUE]; END; delim => NULL; ENDCASE => ERROR; -- bad SType in common Noad node,disc,space => NULL; style => curstyle_qq.s; ENDCASE => ERROR; -- bad Noad type ENDLOOP; RETURN[MlistToHlist[p, style, penalties]]; END; PenaltyNodeFollows: PROCEDURE[p: NoadPtr] RETURNS[BOOLEAN] = --INLINE-- BEGIN q: NoadPtr_p.link; IF q#NIL THEN WITH qq:q SELECT FROM node => IF qq.p#NIL AND qq.p.type=penalty THEN RETURN[TRUE]; ENDCASE; RETURN[FALSE]; END; InterElementGlue: PROCEDURE[a,b: MType, size: MathSize] RETURNS[GlueNodePtr] = --INLINE-- BEGIN g: GlueNodePtr_NIL; quad: Dimn_MathFontPar[quad,size]; SELECT SpaceTable[a,b] FROM no => NULL; -- no space thin => g_MathGlue[thinGlue, quad]; th => IF size=text THEN g_MathGlue[thinGlue, quad]; thick => IF size=text THEN g_MathGlue[thickGlue, quad]; op => IF size=text THEN g_MathGlue[opGlue, quad]; ENDCASE => ERROR TexErrorDefs.Confusion; -- invalid SpaceTable entry RETURN[g]; END; NullMField: PROCEDURE[f: MFieldPtr] RETURNS[BOOLEAN] = --INLINE-- BEGIN WITH ff:f SELECT FROM box => RETURN[ff.box=NIL]; ENDCASE; RETURN[FALSE]; END; KernScript: PROCEDURE[np: ScriptedNoadPtr] RETURNS[BOOLEAN] = --INLINE-- BEGIN RETURN[NullMField[@np.supscr] AND NOT NullMField[@np.subscr]]; END; BoxOp: PROCEDURE[op: MFieldPtr, style: MathStyle] = --INLINE-- BEGIN -- check for a single character op in \mathex singlchrxop: BOOLEAN_FALSE; WITH ff:op SELECT FROM mchar => IF ff.mchar.mfont=ex THEN BEGIN singlchrxop_TRUE; IF style.style=disp THEN BEGIN OPEN TexFontDefs; ltype: LargerType; linfo: LargerInfo; [ltype,linfo]_NextLarger[MCharToFChar[ff.mchar,text]]; WITH linfo SELECT ltype FROM nextlarger => ff.mchar.char_next; -- use larger size if available ENDCASE; END; END; ENDCASE; BoxField[op, style, TRUE]; IF singlchrxop THEN WITH ff:op SELECT FROM box => BEGIN b: BoxNodePtr_ff.box; b.shiftamt_-MathPar[axisheight,FontSize[style]]-b.depth/2; -- shift the character so that its height above the axis -- exceeds its depth below the axis by the character height END; ENDCASE => ERROR WrongMFieldType; END; BoxField: PUBLIC PROCEDURE[f: MFieldPtr, style: MathStyle, corr: BOOLEAN] = BEGIN -- This procedure converts a noad field into the corresponding box. -- If corr is true, the italic correction occurs at the right of a -- single-character box. Recursion comes about when BoxField calls -- EvalMlist which calls BoxField. WITH ff:f SELECT FROM box => RETURN; -- nothing to do if already boxed mlist => f^_[box[BoxNode[EvalMlist[ff.mlist, style, FALSE]]]]; mchar => f^_[box[BoxChar[ff.mchar, style, corr].box]]; ENDCASE => ERROR; -- invalid MField tag END; BoxNode: PROCEDURE[q: NodePtr] RETURNS[BoxNodePtr] = --INLINE-- BEGIN list: NodeListPtr; IF q=NIL THEN RETURN[NIL]; WITH qq:q SELECT FROM box => IF qq.link=NIL THEN RETURN[@qq]; ENDCASE; list_InitNodeList[]; list.link_q; list.last_NIL; RETURN[TexPackDefs.HBox[list]]; END; -- initialization MathBInit; END.