-- Statement.mesa
-- last modified by Sweet, 25-Mar-82 15:33:51
-- last modified by Satterthwaite, January 11, 1983 4:55 pm

DIRECTORY
  Alloc: TYPE USING [Notifier],
  CatchFormat: TYPE USING [cEnable, cReject, defaultFsi],
  Code: TYPE USING [
    actenable, caseCVState, catchcount, catchoutrecord, 
    CodeNotImplemented, codeptr, codeStart, curctxlvl, enableLevel, 
    fileindex, framesz, 
    inlineFileIndex, StackNotEmptyAtStatement, xtracting],
  CodeDefs: TYPE USING [
    Base, BYTE, CaseCVState, CCIndex, CCItem, codeType, EnableIndex, 
    JumpType, LabelCCIndex, LabelCCNull, LabelInfoIndex, Lexeme, 
    NULLfileindex, NullLex, OtherCCIndex, StackIndex, TempStateRecord, 
    VarComponent, VarIndex],
  ComData: TYPE USING [bodyIndex, switches, textIndex],
  FOpCodes: TYPE USING [
    qBC, qBNDCK, qCATCH, qCATCHFSI, qDADD, qDCMP, qDEC, qDSK, qDSUB, 
    qINC, qLP, qLST, qLSTE, qLSTF, qNC, qREC, qRET, qUDCMP],
  Log: TYPE USING [Error, Warning],
  P5: TYPE USING [
    BindStmtExp, CaseStmtExp, CaseTest, Exp, FlowTree, GenAnonLex, GenHeapLex,
    GetLabelMark, LabelCreate, LabelList, LogHeapFree, MakeExitLabel, P5Error,
    PopInVals, PopTempState, PurgeHeapList, PurgePendTempList, PushHeapList,
    PushLex, PushRhs, PushTempState, ReleaseTempLex, SAssign, SysCall, SysError,
    TTAssign],
  P5L: TYPE USING [LoadAddress, MakeComponent, VarForLex],
  P5S: TYPE USING [
    Assign, Call, CatchMark, Continue, Exit, Extract, Free, GoTo, Join, Label, Lock, 
    Loop, ProcInit, Restart, Result, Resume, Retry, Return, RetWithError, 
    SigErr, Start, Stop, Subst, Unlock, Wait],
  P5U: TYPE USING [
    BeginCatch, CCellAlloc, ComputeFrameSize, EndCatch, InsertLabel,
    LabelAlloc, NewEnableItem, Out0, Out1, OutCatchMark, OutJump, OutSource,
    PushLitVal, TreeLiteralValue, WordsForOperand],
  PrincOps: TYPE USING [AVHeapSize, localbase],
  Stack: TYPE USING [
    Clear, Decr, Depth, Incr, Mark, New, Off, On, Pop, 
    Reset, Restore],
  SymbolOps: TYPE USING [TransferTypes],
  Symbols: TYPE USING [
    Base, bodyType, BTIndex, BTNull, CCBTIndex, CCBTNull, ContextLevel,
    CSEIndex, CSENull, CTXIndex, CTXNull, ctxType,
    ISEIndex, ISENull, RecordSEIndex, RecordSENull, seType],
  Tree: TYPE USING [Base, Index, Link, Map, NodeName, Null, Scan, treeType],
  TreeOps: TYPE USING [
    FreeTree, GetNode, GetSe, MarkShared, ReverseUpdateList, ScanList, UpdateList];

Statement: PROGRAM
    IMPORTS MPtr: ComData, CPtr: Code, P5U, P5L, P5, P5S,
      Stack, SymbolOps, TreeOps, Log 
    EXPORTS CodeDefs, P5 =
  BEGIN
  OPEN FOpCodes, CodeDefs;

  -- imported definitions

  ISEIndex: TYPE = Symbols.ISEIndex;
  ISENull: ISEIndex = Symbols.ISENull;
  CSEIndex: TYPE = Symbols.CSEIndex;
  CSENull: CSEIndex = Symbols.CSENull;
  RecordSEIndex: TYPE = Symbols.RecordSEIndex;
  RecordSENull: RecordSEIndex = Symbols.RecordSENull;
  BTIndex: TYPE = Symbols.BTIndex;
  BTNull: BTIndex = Symbols.BTNull;
  CCBTIndex: TYPE = Symbols.CCBTIndex;


  tb: Tree.Base;		-- tree base (local copy)
  seb: Symbols.Base;		-- semantic entry base (local copy)
  ctxb: Symbols.Base;	-- context entry base (local copy)
  cb: CodeDefs.Base;		-- code base (local copy)
  bb: Symbols.Base;		-- body base (local copy)

  StatementNotify: PUBLIC Alloc.Notifier =
    BEGIN  -- called by allocator whenever table area is repacked
    seb ← base[Symbols.seType];
    ctxb ← base[Symbols.ctxType];
    tb ← base[Tree.treeType];
    cb ← base[codeType];
    bb ← base[Symbols.bodyType];
    END;

  catchEndLabel: LabelCCIndex ← LabelCCNull;

  recentStmt: PUBLIC Tree.Link; -- for debugging

  StatementTree: PUBLIC PROC [t: Tree.Link] RETURNS [Tree.Link] =
    BEGIN -- generates code for Mesa statements
    node: Tree.Index;
    saveHeapList: ISEIndex;
    saveIndex: CARDINAL = MPtr.textIndex;
    recentStmt ← t;
    IF t = Tree.Null THEN RETURN [Tree.Null];
    BEGIN
    ENABLE 
      BEGIN
      P5.LogHeapFree => RESUME [TRUE, P5.GenHeapLex[]];
      CPtr.CodeNotImplemented => IF ~MPtr.switches['d] THEN
	GO TO unimplementedConstruct;
      END;
    saveHeapList ← P5.PushHeapList[];
    WITH t SELECT FROM
      subtree =>
	BEGIN
        fIndex: CARDINAL ← CPtr.inlineFileIndex;
	node ← index;
	IF fIndex = NULLfileindex THEN fIndex ← tb[node].info;
        IF fIndex # NULLfileindex THEN
	  SELECT tb[node].name FROM
	    list, block, null => NULL; -- info is not a valid file index
	    ENDCASE => 
	      {CPtr.fileindex ← MPtr.textIndex ← fIndex; P5U.OutSource[fIndex]};
	IF ~CPtr.xtracting AND Stack.Depth[] # 0 THEN
	  {SIGNAL CPtr.StackNotEmptyAtStatement; Stack.Clear[]};
	SELECT tb[node].name FROM
	  list => t ← TreeOps.UpdateList[t, StatementTree];
	  block => Block[node];
	  start => P5S.Start[node];
	  restart => P5S.Restart[node];
	  stop => P5S.Stop[node];
	  dst => DumpState[node];
	  lst =>  LoadState[node];
	  lste => LoadStateEnable[node];
	  lstf => LoadStateFree[node];
	  call, portcall => P5S.Call[node];
	  signal, error => P5S.SigErr[node];
	  syscall => SysCallStmt[node];
	  syserror => P5.SysError[];
	  label => P5S.Label[node];
	  assign => P5S.Assign[node];
	  extract => P5S.Extract[node];
	  if => IfStmt[node];
	  case => [] ← P5.CaseStmtExp[node, FALSE];
	  bind => [] ← P5.BindStmtExp[node, FALSE];
	  do => DoStmt[node];
	  exit => P5S.Exit[];
	  loop => P5S.Loop[];
	  retry => P5S.Retry[];
	  continue => P5S.Continue[];
	  goto => P5S.GoTo[node];
	  catchmark => P5S.CatchMark[node];
	  return => P5S.Return[node];
	  resume => P5S.Resume[node];
	  reject => Reject[];
	  result => P5S.Result[node];
	  open => Open[node];
	  enable => Enable[node];
	  checked => tb[node].son[1] ← StatementTree[tb[node].son[1]];
	  procinit => P5S.ProcInit[node];
	  wait => P5S.Wait[node];
	  notify => Notify[node];
	  broadcast => Broadcast[node];
	  join => P5S.Join[node];
	  unlock => P5S.Unlock[node];
	  lock => P5S.Lock[node];
          subst => P5S.Subst[node];
	  free => P5S.Free[node];
	  xerror => P5S.RetWithError[node];
	  null => NULL;
	  ENDCASE => GO TO unimplementedConstruct;
	END;
      ENDCASE;
    P5.PurgeHeapList[saveHeapList];
    P5.PurgePendTempList[];
    EXITS
      unimplementedConstruct => {Log.Error[unimplemented]; Stack.Clear[]};
    END;
    MPtr.textIndex ← saveIndex;
    RETURN [TreeOps.FreeTree[t]]
    END;


  SysCallStmt: PROC [node: Tree.Index] =
    BEGIN
    Stack.Mark[];
    TreeOps.ScanList[tb[node].son[2], P5.PushRhs];
    P5.SysCall[P5U.TreeLiteralValue[tb[node].son[1]]];
    END;


  Open: PROC [node: Tree.Index] =
    BEGIN
    OPEN TreeOps;

    OpenItem: PROC [t: Tree.Link] RETURNS [Tree.Link] =
      BEGIN
      MarkShared[t, FALSE];
      RETURN [FreeTree[t]]
      END;

    tb[node].son[2] ← StatementTree[tb[node].son[2]];
    tb[node].son[1] ← ReverseUpdateList[tb[node].son[1], OpenItem];
    END;


  DumpState: PROC [node: Tree.Index] = INLINE
    BEGIN -- generates dumpstate
    DLState[node, qDSK];
    END;

  LoadState: PROC [node: Tree.Index] = INLINE
    BEGIN -- generates loadstate and enable
    DLState[node, qLST];
    END;

  LoadStateEnable: PROC [node: Tree.Index] = INLINE
    BEGIN -- generates loadstate and enable
    DLState[node, qLSTE];
    END;

  LoadStateFree: PROC [node: Tree.Index] = INLINE
    BEGIN -- generates loadstateandfree
    DLState[node, qLSTF];
    P5U.OutJump[JumpRet, LabelCCNull];
    END;

  DLState: PROC [node: Tree.Index, opc: BYTE] =
    BEGIN -- does state move after checking for small currentcontext address
    lowBound: CARDINAL = PrincOps.localbase+2;
    var: VarComponent = P5L.MakeComponent[P5L.VarForLex[P5.Exp[tb[node].son[1]]]];
    WITH var SELECT FROM
      frame => 
	BEGIN
	IF level # CPtr.curctxlvl THEN {Log.Error[stateVector]; RETURN};
	IF wd NOT IN [lowBound..BYTE.LAST] THEN Log.Warning[stateVector];
	P5U.Out1[opc, wd];
	END;
      ENDCASE => Log.Error[stateVector];
    END;


  Block: PROC [node: Tree.Index] =
    BEGIN
    bti: BTIndex = tb[node].info;
    EnterBlock[bti, FALSE];
    tb[node].son[1] ← StatementTree[tb[node].son[1]];
    tb[node].son[2] ← StatementTree[tb[node].son[2]];
    ExitBlock[bti];
    END;

  EnterBlock: PUBLIC PROC [bti: BTIndex, catch: BOOL] =
    BEGIN
    IF CPtr.inlineFileIndex = NULLfileindex THEN
      CPtr.fileindex ← MPtr.textIndex ← bb[bti].sourceIndex
    ELSE bb[bti].sourceIndex ← CPtr.inlineFileIndex;
    IF ~catch THEN P5U.OutSource[bb[bti].sourceIndex];
    P5U.CCellAlloc[other];
    cb[LOOPHOLE[CPtr.codeptr, OtherCCIndex]].obody ← markbody[start: TRUE, index: bti];
    END;

  ExitBlock: PUBLIC PROC [bti: BTIndex] =
    BEGIN
    P5U.CCellAlloc[other];
    cb[LOOPHOLE[CPtr.codeptr, OtherCCIndex]].obody ← markbody[start: FALSE, index: bti];
    END;


  IfStmt: PROC [node: Tree.Index] =
    BEGIN -- generates code for an IF statement
    eLabel: LabelCCIndex = P5U.LabelAlloc[];
    P5.FlowTree[tb[node].son[1], FALSE, eLabel
	! P5.LogHeapFree => RESUME [FALSE, NullLex]];
    P5.PurgePendTempList[];
    tb[node].son[2] ← StatementTree[tb[node].son[2]];
    IF tb[node].son[3] # Tree.Null THEN
      BEGIN
      iLabel: LabelCCIndex = P5U.LabelAlloc[];
      P5U.OutJump[Jump, iLabel];
      P5U.InsertLabel[eLabel];
      tb[node].son[3] ← StatementTree[tb[node].son[3]];
      P5U.InsertLabel[iLabel];
      END
    ELSE P5U.InsertLabel[eLabel];
    END;


  DoStmt: PROC [rootNode: Tree.Index] =
    BEGIN --  generates code for all the loop statments
    stepLoop, tempIndex, tempEnd, upLoop, forSeqLoop, bigForSeq: BOOL ← FALSE;
    signed, long: BOOL ← FALSE;
    sSon, eSon: Tree.Link;
    node, subNode: Tree.Index;
    bti: BTIndex ← BTNull;
    intType: Tree.NodeName;
    indexLex: Lexeme.se;
    endLex: Lexeme;
    topLabel: LabelCCIndex = P5U.LabelAlloc[];
    startLabel: LabelCCIndex;
    finLabel: LabelCCIndex = P5U.LabelAlloc[];
    endLabel, loopLabel: LabelCCIndex;
    labelMark: LabelInfoIndex = P5.GetLabelMark[];

    UpdateCV: PROC [loadLong: BOOL] =
      BEGIN
      IF long THEN
        BEGIN
	IF loadLong THEN P5.PushLex[indexLex];
	P5U.PushLitVal[1]; P5U.PushLitVal[0];
	P5U.Out0[IF upLoop THEN qDADD ELSE qDSUB];
	P5.SAssign[indexLex.lexsei];
	END
      ELSE P5U.Out0[IF upLoop THEN qINC ELSE qDEC];
      END;

    -- set up for EXIT clause

    [exit: endLabel, loop: loopLabel] ← P5.MakeExitLabel[];
    TreeOps.ScanList[tb[rootNode].son[5], P5.LabelCreate];

    -- handle initialization node

    IF tb[rootNode].son[1] = Tree.Null THEN P5U.InsertLabel[topLabel]
    ELSE
      BEGIN
      node ← TreeOps.GetNode[tb[rootNode].son[1]];
      bti ← tb[node].info;
      IF bti # BTNull THEN EnterBlock[bti, FALSE];
      SELECT tb[node].name FROM
	forseq =>
	  BEGIN
	  ENABLE P5.LogHeapFree => RESUME [FALSE, NullLex];
	  t1: Tree.Link = tb[node].son[1];
	  t2: Tree.Link = tb[node].son[2];
	  indexLex ← [se[TreeOps.GetSe[t1]]];
	  forSeqLoop ← TRUE;
	  bigForSeq ← P5U.WordsForOperand[t1] > 2;
	  IF bigForSeq THEN {P5.TTAssign[t1, t2]; P5U.InsertLabel[topLabel]}
	  ELSE {P5.PushRhs[t2]; P5U.InsertLabel[topLabel]; P5.SAssign[indexLex.lexsei]};
	  P5.PurgeHeapList[ISENull];
	  END;
	upthru, downthru =>
	  BEGIN
	  ENABLE P5.LogHeapFree => RESUME [FALSE, NullLex];
	  cvBound: Tree.Link = tb[node].son[3];
	  nonempty: BOOL = tb[node].attr1;
	  stepLoop ← TRUE;
	  upLoop ← tb[node].name = upthru;
	  subNode ← TreeOps.GetNode[tb[node].son[2]];
	  intType ← tb[subNode].name;
	  IF tb[subNode].attr1 THEN SIGNAL CPtr.CodeNotImplemented;
	  long ← tb[subNode].attr2;  signed ← tb[subNode].attr3;
	  WITH tb[node].son[1] SELECT FROM
	    subtree => -- son1 is empty
	      {indexLex ← P5.GenAnonLex[IF long THEN 2 ELSE 1]; tempIndex ← TRUE};
	    symbol => indexLex ← Lexeme[se[index]];
	    ENDCASE;
	  IF upLoop THEN {sSon ← tb[subNode].son[1]; eSon ← tb[subNode].son[2]}
	  ELSE
	    BEGIN
	    SELECT intType FROM
	      intCO => intType ← intOC;
	      intOC => intType ← intCO;
	      ENDCASE;
	    sSon ← tb[subNode].son[2];  eSon ← tb[subNode].son[1];
	    END;
	  WITH e: eSon SELECT FROM
	    literal =>
	      WITH e.index SELECT FROM
		word => endLex ← Lexeme[literal[word[lti]]];
		ENDCASE => P5.P5Error[769];
	    symbol =>
	      IF seb[e.index].immutable THEN endLex ← Lexeme[se[e.index]]
	      ELSE
		BEGIN
		endLex ← P5.GenAnonLex[IF long THEN 2 ELSE 1];
		P5.PushRhs[e];  tempEnd ← TRUE;
		WITH endLex SELECT FROM se => P5.SAssign[lexsei]; ENDCASE;
		END;
	    ENDCASE =>
	      BEGIN
	      endLex ← P5.GenAnonLex[IF long THEN 2 ELSE 1];
	      P5.PushRhs[e];  tempEnd ← TRUE;
	      WITH endLex SELECT FROM se => P5.SAssign[lexsei]; ENDCASE;
	      END;
	  startLabel ← P5U.LabelAlloc[];
	  P5.PushRhs[sSon];
	  IF long THEN P5.SAssign[indexLex.lexsei];
	  IF (intType = intCC OR intType = intOO) AND ~nonempty THEN
	    BEGIN -- earlier passes check for empty intervals

	    TopTest: ARRAY BOOL OF
	     ARRAY BOOL OF ARRAY BOOL OF JumpType = [
	      [[UJumpL,UJumpLE],	-- unsigned, down, closed/open
	       [UJumpG,UJumpGE]],	-- unsigned, up, closed/open
	      [[JumpL,JumpLE],		-- signed, down, closed/open
	       [JumpG,JumpGE]]];		-- signed, up, closed/open

	    IF long THEN {P5U.Out0[qREC]; P5U.Out0[qREC]};
	    P5.PushLex[endLex];
	    IF long THEN
	      {P5U.Out0[IF signed THEN qDCMP ELSE qUDCMP]; P5U.PushLitVal[0]};
	    P5U.OutJump[TopTest[long OR signed][upLoop][intType = intOO], finLabel];
	    IF ~long THEN P5U.Out0[qREC];
	    END;
	  IF ~long THEN Stack.Decr[1];
	  P5U.OutJump[Jump, startLabel];
	  P5U.InsertLabel[topLabel];
	  IF ~long THEN P5U.Out0[qREC];
	  SELECT intType FROM
	    intCC => {UpdateCV[TRUE]; P5U.InsertLabel[startLabel]};
	    intOC => UpdateCV[TRUE];
	    intCO, intOO => NULL;
	    ENDCASE;
	  IF ~long THEN
	    BEGIN
	    IF cvBound # Tree.Null
	      THEN {P5.PushRhs[cvBound]; P5U.Out0[FOpCodes.qBNDCK]};
	    P5.SAssign[indexLex.lexsei];
	    END;
	  END;
	ENDCASE;
      END;

    -- now the pre-body test

    IF tb[rootNode].son[2] # Tree.Null THEN
      P5.FlowTree[tb[rootNode].son[2], FALSE, finLabel
	  ! P5.LogHeapFree => RESUME [FALSE, NullLex]];

    -- ignore the opens (tb[rootNode].son3)

    -- now the body

    tb[rootNode].son[4] ← StatementTree[tb[rootNode].son[4]];

    -- now (update and) test the control variable

    P5U.InsertLabel[loopLabel];
    IF stepLoop THEN
      BEGIN
      IF long AND (intType = intOC OR intType = intOO) THEN P5U.InsertLabel[startLabel];
      P5.PushLex[indexLex];
      SELECT intType FROM
	intCC => NULL;
	intCO => {UpdateCV[FALSE]; P5U.InsertLabel[startLabel]};
	intOC => IF ~long THEN P5U.InsertLabel[startLabel];
	intOO => {IF ~long THEN P5U.InsertLabel[startLabel]; UpdateCV[FALSE]};
	ENDCASE;
      IF long THEN SELECT intType FROM
	intCO, intOO => {P5U.Out0[qREC]; P5U.Out0[qREC]};
	ENDCASE;
      P5.PushLex[endLex];
      IF long THEN
	{P5U.Out0[IF signed THEN qDCMP ELSE qUDCMP]; P5U.PushLitVal[0]};
      P5U.OutJump[
	    IF ~long AND ~signed THEN 
	      IF upLoop THEN UJumpL ELSE UJumpG
	    ELSE IF upLoop THEN JumpL ELSE JumpG, topLabel];
      P5U.OutJump[Jump, finLabel];
      IF tempEnd THEN P5.ReleaseTempLex[LOOPHOLE[endLex, Lexeme.se]];
      IF tempIndex THEN P5.ReleaseTempLex[indexLex];
      END
    ELSE
      BEGIN
      IF forSeqLoop THEN
	BEGIN
	ENABLE P5.LogHeapFree => RESUME [FALSE, NullLex];
	IF bigForSeq THEN P5.TTAssign[[symbol[indexLex.lexsei]], tb[node].son[3]]
	ELSE P5.PushRhs[tb[node].son[3]];
	P5.PurgeHeapList[ISENull];
	END;
      P5U.OutJump[Jump, topLabel];
      END;
    Stack.Reset[];
    P5.PurgePendTempList[];

    -- now the labelled EXITs

    P5.LabelList[tb[rootNode].son[5], endLabel, labelMark];

    -- finally the FINISHED clause

    P5U.InsertLabel[finLabel];
    tb[rootNode].son[6] ← StatementTree[tb[rootNode].son[6]];
    IF bti # BTNull THEN ExitBlock[bti];
    P5U.InsertLabel[endLabel];
    END;


  CatchPhrase: PUBLIC PROC [node: Tree.Index] =
    BEGIN -- process a catchphrase at procedure call
    bti: CCBTIndex = tb[node].info;
    
    CPtr.catchcount ← CPtr.catchcount + 1;
    P5U.Out1[qCATCH, bb[bti].index];
    SCatchPhrase[node];
    CPtr.catchcount ← CPtr.catchcount - 1;
    END;


  Enable: PROC [node: Tree.Index] =
    BEGIN -- generate code for an ENABLE
    saveActEnable: CCBTIndex = CPtr.actenable;
    n1: Tree.Index = TreeOps.GetNode[tb[node].son[1]];
    bti: CCBTIndex = tb[n1].info;
    ei: EnableIndex = P5U.NewEnableItem[bti];
    
    CPtr.catchcount ← CPtr.catchcount + 1;
    SCatchPhrase[n1];
    CPtr.actenable ← bti;
    CPtr.enableLevel ← CPtr.enableLevel + 1;
    CPtr.catchcount ← CPtr.catchcount - 1;
    P5U.OutCatchMark[index: ei, start: TRUE];
    tb[node].son[2] ← StatementTree[tb[node].son[2]];
    P5U.OutCatchMark[index: ei, start: FALSE];
    CPtr.enableLevel ← CPtr.enableLevel - 1;
    CPtr.actenable ← saveActEnable;
    END;


  SCatchPhrase: PUBLIC PROC [node: Tree.Index] =
    BEGIN -- main subr for catchphrases and ENABLEs
    first, cur: CCIndex;
    saveCaseCVState: CaseCVState = CPtr.caseCVState;
    saveEndLabel: LabelCCIndex = catchEndLabel;
    oldStkPtr: StackIndex = Stack.New[];
    saveActEnable: CCBTIndex = CPtr.actenable;
    saveEnableLevel: CARDINAL = CPtr.enableLevel;
    tempState: TempStateRecord;
    bti: CCBTIndex = tb[node].info;
    initialFrameSize, cfsi: NAT;

    CatchScan: PROC [t: Tree.Link] =
      BEGIN
      fail: LabelCCIndex = P5U.LabelAlloc[];
      [] ← CatchItem[node:TreeOps.GetNode[t], failLabel: fail];
      P5U.OutJump[Jump, catchEndLabel];
      P5U.InsertLabel[fail];
      END;

    WITH bb[bti].info SELECT FROM
      Internal => initialFrameSize ← frameSize;
      ENDCASE => ERROR;
      
    catchEndLabel ← P5U.LabelAlloc[];
    CPtr.curctxlvl ← CPtr.curctxlvl + 1;
    P5.PushTempState[@tempState, initialFrameSize];
    
    Stack.Incr[1]; -- signal code on stack
    CPtr.caseCVState ← singleLoaded;
    CPtr.actenable ← Symbols.CCBTNull;
    [first: first, cur: cur] ← P5U.BeginCatch[];
    EnterBlock[bti, TRUE];
    TreeOps.ScanList[tb[node].son[1], CatchScan];
    IF tb[node].son[1] = Tree.Null THEN Stack.Pop[];
    IF tb[node].son[2] # Tree.Null THEN 
      tb[node].son[2] ← StatementTree[tb[node].son[2]];
    CPtr.actenable ← saveActEnable;
    CPtr.enableLevel ← saveEnableLevel;
    P5U.InsertLabel[catchEndLabel];
    Stack.Off[];
    IF CPtr.actenable # BTNull THEN
      BEGIN
      P5U.PushLitVal[bb[CPtr.actenable].index];
      P5U.PushLitVal[CatchFormat.cEnable];
      P5U.Out0[qRET];  P5U.OutJump[JumpRet,LabelCCNull];
      END
    ELSE
      BEGIN
      P5U.PushLitVal[CatchFormat.cReject];
      P5U.Out0[qRET];  P5U.OutJump[JumpRet,LabelCCNull];
      END;
    Stack.On[];
    ExitBlock[bti];
    CPtr.curctxlvl ← CPtr.curctxlvl-1;
    CPtr.caseCVState ← saveCaseCVState;
    catchEndLabel ← saveEndLabel;
    cfsi ← P5U.ComputeFrameSize[CPtr.framesz];
    P5.PopTempState[@tempState];
    IF bb[MPtr.bodyIndex].resident THEN 
      cfsi ← cfsi + PrincOps.AVHeapSize;
    IF cfsi > CatchFormat.defaultFsi THEN {
      CPtr.codeptr ← cb[CPtr.codeStart].flink; -- the startbody node
      P5U.Out1[FOpCodes.qCATCHFSI, cfsi]};
    P5U.EndCatch[oldfirst: first, oldcur: cur];
    Stack.Restore[oldStkPtr];
    END;

  CatchItem: PROC [node: Tree.Index, failLabel: LabelCCIndex] =
    BEGIN -- generate code for a CATCH item
    saveCatchOutRecord: RecordSEIndex = CPtr.catchoutrecord;
    inRecord: RecordSEIndex;
    tSei: CSEIndex = tb[node].info;
    saveInCtxLevel, saveOutCtxLevel: Symbols.ContextLevel;
    inCtx, outCtx: Symbols.CTXIndex ← Symbols.CTXNull;
    P5.CaseTest[tb[node].son[1], failLabel];
    IF tSei = CSENull THEN inRecord ← CPtr.catchoutrecord ← RecordSENull
    ELSE
      BEGIN
      [inRecord, CPtr.catchoutrecord] ← SymbolOps.TransferTypes[tSei];
      IF inRecord # RecordSENull THEN
	    BEGIN
	    inCtx ← seb[inRecord].fieldCtx;
	    saveInCtxLevel ← ctxb[inCtx].level;
	    ctxb[inCtx].level ← CPtr.curctxlvl;
	    END;
      IF CPtr.catchoutrecord # RecordSENull THEN
	    BEGIN
	    outCtx ← seb[CPtr.catchoutrecord].fieldCtx;
	    saveOutCtxLevel ← ctxb[outCtx].level;
	    ctxb[outCtx].level ← CPtr.curctxlvl;
	    END;
      P5.PopInVals[inRecord, TRUE];
      END;
    tb[node].son[2] ← StatementTree[tb[node].son[2]];
    IF inCtx # Symbols.CTXNull THEN ctxb[inCtx].level ← saveInCtxLevel;
    IF outCtx # Symbols.CTXNull THEN ctxb[outCtx].level ← saveOutCtxLevel;
    CPtr.catchoutrecord ← saveCatchOutRecord;
    END;


  Reject: PROC = INLINE
    BEGIN
    P5U.OutJump[Jump,catchEndLabel];
    END;

  Notify: PROC [node: Tree.Index] =
    BEGIN
    r: VarIndex = P5L.VarForLex[P5.Exp[tb[node].son[1]]];
    IF ~P5L.LoadAddress[r].long THEN P5U.Out0[qLP];
    P5U.Out0[qNC];
    END;

  Broadcast: PROC [node: Tree.Index] =
    BEGIN
    r: VarIndex = P5L.VarForLex[P5.Exp[tb[node].son[1]]];
    IF ~P5L.LoadAddress[r].long THEN P5U.Out0[qLP];
    P5U.Out0[qBC];
    END;

  END.