{ History ------- 11/09/85 - new include file eput.pf, expand AccessArea, AddressArea, - LoadIndirect, AdjustAddress, LoadAccess, AdjustLoad - amend LoadAddress, Load 23/09/85 - new include file impint.pf, expand InLineNumber, InLineReal, InLineMutipleConst, JumpTo; amend AccessArea, Addressarea, DoUnaryOp, DoBinaryOp 07/10/85 - amend LoadAddress for CAPIndex & AConstant, amend SaveAddress, DoCAPLoad, SaveValue & LoadValue 21/10/85 - pascal specific opcodes called by Epasop 23/10/85 - DoReadOp completed with calls to i/o E-codes. (agh) 25/10/85 - All outstanding Pascal specific E-codes added. (agh) 28/10/85 - Remove all references to ancillary checklist. Add calls to special E-codes to perform lazy i/o checks and tailored-factor check. (agh) 04/11/85 - calls to AccessArea and AddressArea simplified to reduce number of parameters. (agh) 06/11/85 - Add DoICLStandardOp for ICL operations. (agh) 07/11/85 - Add CVTII to DoUnaryOp. (agh) 08/11/85 - Provide complete evaluation of compund Boolean expressions. 25/11/85 - Provide word-operations via DoBinaryOp and DoICLStandardOp. (agh). 29/11/85 - Use class = HeapRef to trigger the tailored factor check. (agh) 02/12/85 - Many changes to provide access to bit-fields of packed and nested packed structures. (agh) 04/12/85 - Remove CHKATFR, CGKCTFR and replace by manual E-codes. (agh) 04/12/85 - Re-implement CAPLoad and CAPSize. (agh) 04/12/85 - Re-implement conformant array indexing using existing P-codes. (agh) 05/12/85 - Re-implement range-checking to allow constant and non-constant bounds. (agh) 06/12/85 - Provide PushValue, PushAddress, PushLiteral, StartCall and CallStdrd for call run-time system routines. (agh) 09/12/85 - Re-name Pascal E-codes for consistency. (agh) 09/12/85 - Modify PushAddr to use Eop(PUSHVAL). (agh) --------------------------------------------------------------------- 17/12/85 - Change occurrences of CHKUP, UCHKUP, and CHKSETUP. (agh) 20/12/85 - Supply correct constant length in LoadMultipleConst. (agh) 03/01/86 - Add LoadStringConst for passing string-constant as an imp-string with leading length byte. (agh) 09/01/86 - Make Exname call for an rt routine prior to the first call of the routine in StartCall. (agh) --------------------------------------------------------------------- 29/01/86 - remove calll on CHKNEW2 from LoadAdress 04/02/86 - use BNOT for Boolean negation. - Replace 0 by MCBytesPerWord in calls to Refer. - Make explicit call to CVTII for ord in STandardOP. - Restore treatment for multiple-consts passed as actual - readonly parameters. - Call EstkResult in DoReadOp & DoStandardOp. ---------------------------------------------------------------------- 06/02/86 - Call EstkResult in DoStandardOP at Areal:. 13/02/86 - Enalbe calls to EpRestore & EpSave. Make appropriate CVTRR calls when passing single-precision real parameters to the maths functions. Initialise StackedBitField in LoadAddress. Insert call to CVTII in LOad for packed-field access. Add size attribute to post-indexing call to Eprefer. In LoadAddress suppress address adjustment for bit-field. } { MODULE 19 Data Access Code Generation This chapter defines the code generation utilities on which subse- quent code generation procedures depend. The facilities provided include: (a) generation of code to load the address implied by a reference held as an access list, together with the generation of ancillary access checks as described in Chapter 16; (b) generation of code to load and check the value implied by an expression tree, as described in Chapter 17; (c) temporary value storage and re-loading. The procedures InlineNumber, InlineReal and InlineWord generate the ConstX instructions which load literal values from the code itself. The procedure InlineMultipleConst is used to embed multi-word images in ConstMultiple and ConstRefMultiple instruc- tions. } program AccessGenerator; #include "globals.x" #include "generator.pf" #include "datareps.pf" #include "storage.pf" #include "varref.pf" #include "stdprocs.pf" #include "ctlstructs.pf" #include "pfcalls.pf" #include "eput.pf" #include "impint.pf" procedure InlineNumber(Number: MCIntegerForm); visible; begin Estklit(Number) end; procedure LoadReal(RealNumber: MCRealForm); var Buffer: LiteralBuffer; RealMap: record case Boolean of false: (RealValue: MCRealForm); true: (Words: array [1..MCMaxRealSize] of MCWord) end; i: 1..MCMaxRealSize; begin RealMap.RealValue := RealNumber; for i := 1 to MCRealSize do Buffer[i] := RealMap.Words[i]; Estkconst(MCRealSize * MCBytesPerWord, MCAddress(wptr(Buffer))) end { loadreal }; procedure LoadMultipleConst(TheConst: ObjectValue); var NextWord: WordEntry; WordCount, ByteCount: Scalar; Buffer: LiteralBuffer; begin with TheConst do begin if Kind = SetValue then NextWord := Setval else NextWord := Stringval; WordCount := 0; while NextWord <> nil do begin WordCount := WordCount + 1; Buffer[WordCount] := NextWord^.Word.WValue; NextWord := NextWord^.Next end; while WordCount < WordSize do begin WordCount := WordCount + 1; Buffer[WordCount] := 0 end; if Kind = SetValue then ByteCount := WordCount * MCBytesPerWord else ByteCount := Length; Estkconst(ByteCount, MCAddress(wptr(Buffer))) end end { loadmultipleconst }; procedure LoadStringConst(TheConst: ObjectValue); var StringBuffer: ImpStr; StringWord: WordEntry; ByteIndex: MCByteIndex; ByteValue: MCByte; i: 0..MaxImpStr; begin with TheConst do begin StringWord := StringVal; ByteIndex := 0; for i := 1 to Length do begin MCGetByte(StringWord^.Word, ByteIndex, ByteValue); StringBuffer[i] := chr(ByteValue); ByteIndex := (ByteIndex + 1) mod MCBytesPerWord; if ByteIndex = 0 then StringWord := StringWord^.Next end; StringBuffer[0] := chr(Length); Estkconst(Length + 1, MCAddress(wptr(StringBuffer))) end end { LoadStringConst }; { 19.2 Generating Jump Instructions } procedure JumpTo(var TheLabel: CodeLabel; Condition: JumpType); visible; begin case Condition of IfFalse : Ejump(JFALSE, TheLabel); IfTrue : Ejump(JTRUE, TheLabel); Absolute : Ejump(JUMP, TheLabel) end end { jumpto }; { 19.4 Data Access Utilities } procedure AccessArea(Address: RuntimeAddress; Adjustment: ByteOffsets; Size: ByteRange); visible; begin with Address do case Area of Stack : Estkglobal(BlockLevel, ByteOffset + Adjustment, Adid, Size); Parameter : Estkparam(BlockLevel, ByteOffset + Adjustment, Adid, Size); Gla, GST, Static : Estkdir(Area, ByteOffset + Adjustment, Adid, Size); end end { AccessArea }; procedure AddressArea(Address: RuntimeAddress; Adjustment: ByteOffsets; Size: ByteRange); visible; begin with Address do case Area of Stack : Estkgaddr(BlockLevel, ByteOffset + Adjustment, Adid, Size); Parameter : Estkpaddr(BlockLevel, ByteOffset + Adjustment, Adid, Size); Gla, GST, Static : Estkaddr(Area, ByteOffset + Adjustment, Adid, Size); end end { AddressArea }; procedure LoadIndirect; begin Erefer(0, MCBytesPerWord) end; procedure AdjustAddress(Offset: ByteOffsets); begin Erefer(Offset, MCBytesPerWord); Eop(EADDRESS) end; procedure LoadAccess(Size: ByteRange); begin Erefer(0, Size) end; procedure AdjustLoad(Offset: ByteOffsets; Size: ByteRange); begin Erefer(Offset, Size) end; procedure LoadBuffer(Size: ByteRange); begin Epasop(LAZYOP) end; { 19.5 Loading and Saving Addresses The procedure LoadAddress is used to generate the code required to load the address implied by an access list, as defined in Chapter 16, and to carry out any ancillary access checks required at each access step. The logic used by LoadAddress follows directly from the form of access lists defined in Chapter 13. The procedure CheckAccess generates the code to apply any access checks required at each step. The procedure SaveAddress is used to preserve an address for sub- sequent re-use if necessary, by acquiring temporary stack frame locations and generating code to store the address there. An address saved in this way is represented by a stack record of variant Address. Both Load and LoadAddress issue E-code calls to perform data-access code-generation for the target-machine. No assumptions are made on the point at which code is actually generated, and it is assumed that this is totally controlled from within the E-machine code- generator itself. } procedure Load(Entry: StackEntry); visible; forward; procedure Normalise(WordBounds: Boolean); begin if WordBounds then Eop(USUB) else Eop(ISUB) end { Normalise }; procedure LoadAddress(Entry: StackEntry); visible; var NextIndex, ThisIndex: IndexEntry; StackedBitField, ElSizeKnown: Boolean; begin with Entry^ do begin case Kind of Reference : begin StackedBitField := false; { load base address } if AccessList <> nil then begin with AccessList^ do if Kind = Reference then StackedBitField := (AccessKind = Bits) else if Kind = Address then StackedBitField := not Loaded and ABitField; LoadAddress(AccessList); if Indirect then LoadIndirect; if not StackedBitField then AdjustAddress(Adjustment); FreeEntry(AccessList); AccessList := nil end else if Indirect then begin AccessArea(BaseAddress, 0, MCBytesPerWord); { if Class = PnterRef then Epasop(CHKNEW2); } AdjustAddress(Adjustment) end else AddressArea (BaseAddress, Adjustment, MCBytesPerWord); { now index or address packed field } if AccessKind = Bits then if IndexedBitField then begin with FieldIndex^ do begin Load(TheIndex); if CAPIndex then AccessArea(BpAddress, 0, MCBytesPerWord) else Estklit(Lower); Normalise(WordBounds); Estklit(Factor); Epasop(INDEXP); FreeEntry(TheIndex); Eprefer(BitOffset, BitSize) end; dispose(FieldIndex) end else if StackedBitField then Eprefer(BitOffset, BitSize) else Estkpf(BitOffset, BitSize) else if Indexed then begin NextIndex := Indices; repeat ThisIndex := NextIndex; with ThisIndex^ do begin Load(TheIndex); if CAPIndex then ElSizeKnown := LastLevel else ElSizeKnown := true; if not ElSizeKnown then begin AccessArea(BpAddress, 0, MCBytesPerWord); Normalise(WordBounds); AccessArea (BpAddress, 2 * MCBytesPerWord, MCBytesPerWord); Eop(INDEX) end else begin if CAPIndex or WordBounds then begin if CAPIndex then AccessArea (BpAddress, 0, MCBytesPerWord) else Estklit(Lower); Normalise(WordBounds) end; if Factor in [1, 2, 4, 8] then case Factor of 1 : Eop(INDEX1); 2 : Eop(INDEX2); 4 : Eop(INDEX4); 8 : Eop(INDEX8); end else begin Estklit(Factor); Eop(INDEX) end end; NextIndex := Next; FreeEntry(TheIndex) end; dispose(ThisIndex) until NextIndex = nil end end; AConstant : begin LoadMultipleConst(TheConst); Eop(EADDRESS) end ; Address : if not Loaded then EpRestore(Descriptor) ; end; Kind := Address; Loaded := true end end { LoadAddress }; procedure SaveAddress(LocalBase: StackEntry); visible; var IndexedRef: Boolean; begin with LocalBase^ do begin if AccessKind = Bits then IndexedRef := IndexedBitField else IndexedRef := Indexed; if (Indirect and (Class = PnterRef)) or (AccessList <> nil) or IndexedRef then begin LoadAddress(LocalBase); Loaded := false; ABitField := (AccessKind = Bits); EpSave(Descriptor) end end end { saveaddress }; { 19.6 Evaluating Expressions The procedure Load is used to generate the code required to load the result of evaluating an expression tree, as defined in Chapter 17. The logic usd by Load follows directly from the form of expression trees, the operations that they represent, and the P-codes avail- able for their implementation. Range checks applicable to inter- mediate and final values are handled as explicit operations within the tree evaluation logic but the implicit undefined value checks applicable when a variable value is loaded are implemented by the auxiliary procedure CheckValue. } procedure StartCall(Routine: Intrinsic); visible; begin with RtSystem[Routine] do begin if LabelId = -1 then LabelId := pasexnm(0, Adid); Eprecall(LabelId) end end { StartCall }; procedure CallStdrd(Routine: Intrinsic); visible; begin with RtSystem[Routine] do Ecall(LabelId, PNumber, PSize) end { CallStdrd }; procedure PushValue(Entry: StackEntry); visible; begin Load(Entry); Eop(PUSHVAL) end { PushValue }; procedure PushAddress(Entry: StackEntry); visible; begin LoadAddress(Entry); Eop(PUSHVAL) end { PushAddress }; procedure PushLiteral(Literal: integer); visible; begin Estklit(Literal); Eop(PUSHVAL) end { PushLiteral }; procedure PushString(StrEntry: StackEntry); visible; begin LoadStringConst(StrEntry^.TheConst); Eop(EADDRESS); Eop(PUSHVAL) end { PushString }; procedure CheckLoadedValue(Entry: StackEntry); visible; begin with Entry^ do if DataRep.Kind in [ForScalar, ForChar, ForSet, ForPnter] then begin Estklit(RunError); Epasop(CHKUNDEF) end end { checkloadedvalue }; procedure Load {Entry : StackEntry}; var CheckNeeded: Boolean; AccessSize: ByteRange; procedure DoBooleanOp; var ThisEntry, NextEntry: StackEntry; FirstOperand: Boolean; OpCode: Ecodes; begin with Entry^ do begin if BooleanOp = OrOp then Opcode := IOR else OpCode := IAND; ThisEntry := OpList; FirstOperand := true; while ThisEntry <> nil do begin NextEntry := ThisEntry^.NextNode; Load(ThisEntry); if FirstOperand then FirstOperand := false else Eop(OpCode); FreeEntry(ThisEntry); ThisEntry := NextEntry end end end { dobooleanop }; procedure DoUnaryOp; var OpCode: Ecodes; begin with Entry^ do begin Load(UnaryEntry); case OpGroup of AnInteger : case UnaryOp of NegateOp : Opcode := INEG; FloatOp : begin Estklit(MCRealSize * MCBytesPerWord); OpCode := CVTIR end; ConvertOp : begin Estklit(DataRep.ByteSize); OpCode := CVTII end end; AReal : OpCode := RNEG; ABoolean : OpCode := BNOT; ASet : OpCode := SETSING end; if OpGroup = ASet then begin Estklit(DataBytes(DataRep)); Epasop(OpCode) end else eop(OpCode); FreeEntry(UnaryEntry) end end { dounaryop }; procedure DoBinaryOp; begin with Entry^ do begin case OpGroup of AnInteger : begin Load(LeftEntry); Load(RightEntry); Eop(IntOps[BinaryOp]) end; AWord : begin Load(LeftEntry); Load(RightEntry); Epasop(WordOps[BinaryOp]) end; AReal : begin Load(LeftEntry); Load(RightEntry); Eop(RealOps[BinaryOp]) end; APointer : begin Load(LeftEntry); Load(RightEntry); Epasop(PtrOps[BinaryOp]) end; AString : begin Load(LeftEntry); Load(RightEntry); Estklit(LeftEntry^.StringBytes); Epasop(StringOPs[BinaryOp]) end; ASet : begin Load(LeftEntry); Load(RightEntry); if BinaryOp = RangeOp then Estklit(DataBytes(DataRep)); Epasop(SetOps[BinaryOp]) end; ACAP : begin LoadAddress(LeftEntry); Load(RightEntry) end end; FreeEntry(LeftEntry); FreeEntry(RightEntry) end end { dobinaryop }; procedure DoBlockCall; begin with Entry^ do begin FnBlockEntry^.CallToBeGenerated := true; Push(FnBlockEntry); CallBlock end end { doblockcall }; procedure DoSubrangeChecks; var MinTestNeeded, MaxTestNeeded: Boolean; CheckOp: Ecodes; begin with Entry^ do begin Load(EntryToCheck); with RequiredRange^ do begin with Lower do if Constant then if EntryToCheck^.DataRep.Min < Value then begin Estklit(Value); MinTestNeeded := true end else MinTestNeeded := false else begin AccessArea(Address, 0, MCBytesPerWord); MinTestNeeded := true end; with Upper do if Constant then if EntryToCheck^.DataRep.Max > Value then begin Estklit(Value); MaxTestNeeded := true end else MaxTestNeeded := false else begin AccessArea(Address, 0 , MCBytesPerWord); MaxTestNeeded := true end; CheckOp := CheckOps[MinTestNeeded, MaxTestNeeded]; if CheckOp <> NOOP then begin Estklit(RunError); Epasop(CheckOp) end end; dispose(RequiredRange); FreeEntry(EntryToCheck) end end { dosubrangechecks }; procedure DoWSubrangeChecks; var MinTestNeeded, MaxTestNeeded: Boolean; CheckOp: Ecodes; begin with Entry^ do begin Load(EntryToCheck); with RequiredRange^ do begin with Lower do if Constant then if EntryToCheck^.DataRep.WMin < wrd(Value) then begin Estklit(Value); MinTestNeeded := true end else MinTestNeeded := false else begin AccessArea(Address, 0 ,MCBytesPerWord); MinTestNeeded := true end; with Upper do if Constant then if EntryToCheck^.DataRep.WMax > wrd(Value) then begin Estklit(Value); MaxTestNeeded := true end else MaxTestNeeded := false else begin AccessArea(Address, 0, MCBytesPerWord); MaxTestNeeded := true end; CheckOp := UCheckOps[MinTestNeeded, MaxTestNeeded]; if CheckOp <> NOOP then begin Estklit(RunError); Epasop(CheckOp) end end; dispose(RequiredRange); FreeEntry(EntryToCheck) end end { dowsubrangechecks }; procedure StackBound(Bound: BoundForm); begin with Bound do if Constant then Estklit(Value) else AccessArea(Address, 0, MCBytesPerWord) end { StackBound }; procedure DoTransferChecks; begin with Entry^ do begin Load(EntryToCheck); with RequiredRange^ do StackBound(Upper); with TransferRange^ do begin StackBound(Upper); StackBound(Lower) end; Eop(ISUB); Eop(ISUB); Estklit(RunError); Epasop(CHKGT); dispose(RequiredRange); dispose(TransferRange); FreeEntry(EntryToCheck) end end { dotransferchecks }; procedure DoWTransferChecks; begin with Entry^ do begin Load(EntryToCheck); with RequiredRange^ do StackBound(Upper); with TransferRange^ do begin StackBound(Upper); StackBound(Lower) end; Eop(USUB); Eop(USUB); Estklit(RunError); Epasop(UCHKGT); dispose(RequiredRange); dispose(TransferRange); FreeEntry(EntryToCheck) end end { dowtransferchecks }; procedure DoMembershipChecks; begin with Entry^ do begin Load(EntryToCheck); with RequiredRange^ do if Lower.Value <> 0 then begin StackBound(Lower); StackBound(Upper); Estklit(RunError); Epasop(CHKSETRNG) end else begin StackBound(Upper); Estklit(RunError); Epasop(CHKSETGT) end; FreeEntry(EntryToCheck) end end { domembershipchecks }; procedure DoReadOp; var Routine: Intrinsic; begin with Entry^ do begin if Mode = IntKind then Routine := p_readi else Routine := p_readr; StartCall(Routine); LoadFCBAddress; CallStdrd(Routine); if Routine = p_readi then Estkresult(0, 1, MCBytesPerWord) else Estkresult(0, 2, MCRealSize * MCBytesPerWord) end end { doreadop }; procedure DoCAPSize; begin with Entry^ do if SizeKnown then AccessArea(BpAddress, 2 * MCBytesPerWord, MCBytesPerWord) else begin AccessArea(BpAddress, MCBytesPerWord, MCBytesPerWord); AccessArea(BpAddress, 0, MCBytesPerWord); if WordBounds then begin Eop(USUB); Epasop(USUCC) end else begin Eop(ISUB); Epasop(ISUCC) end; AccessArea(BpAddress, 2 * MCBytesPerWord, MCBytesPerWord); Eop(IMULT) end end { docapsize }; procedure DoStandardOp; begin with Entry^ do begin case OpGroup of AnInteger : begin Load(StdEntry); case StdOp of Absf : Eop(IABS); Sqrf : Epasop(ISQR); Oddf : Epasop(IODD); Succf : Epasop(ISUCC); Predf : Epasop(IPRED); Ordf : begin Estklit(MCBytesPerWord); Eop(CVTII); end; Chrf : end; FreeEntry(StdEntry) end; AReal : if StdOp in [Sinf, Cosf, Expf, Lnf, Sqrtf, Arctanf] then begin StartCall(SystemRoutine[StdOp]); Load(StdEntry); if MCRealSize =1 then begin Estklit(2 * MCBytesPerWord); Eop(CVTRR) end; Eop(PUSHVAL); CallStdrd(SystemRoutine[StdOp]); EstkResult(0,2,MCRealSize * MCBytesPerWord); if MCRealSize = 1 then begin Estklit(MCBytesPerWord); Eop(CVTRR) end; FreeEntry(StdEntry) end else begin Load(StdEntry); case StdOp of Absf : Eop(RABS); Sqrf : Epasop(RSQR); Truncf : begin Estklit(MCBytesPerWord); Eop(TNCRI) end; Roundf : begin Estklit(MCBytesPerWord); Eop(RNDRI) end end; FreeEntry(StdEntry) end; AFile : begin RstoreFile(IOEntry); StartCall(SystemRoutine[StdOp]); LoadFCBAddress; CallStdrd(SystemRoutine[StdOp]); EstkResult(0, 1, MCBytesPerWord); DiscardFile end end end end { dostandardop }; procedure DoICLStandardOp; begin with Entry^ do case ICLOp of Sizef : ; CAPSizef : begin Load(FirstEntry); Estklit(MCBitsPerByte); Eop(IMULT); FreeEntry(FirstEntry) end; Ptrf, CPtrf : begin LoadAddress(FirstEntry); FreeEntry(FirstEntry) end; Wrdf, Intf, Ordf, Chrf : begin Load(FirstEntry); FreeEntry(FirstEntry) end; Oddf, Succf, Predf : begin Load(FirstEntry); case ICLOp of Oddf : Epasop(UODD); Succf : Epasop(USUCC); Predf : Epasop(UPRED) end; FreeEntry(FirstEntry) end; NotWf : begin Load(FirstEntry); Eop(INOT); FreeEntry(FirstEntry) end; AndWf, OrWf, NeqWf, ShWf, RotWf : begin Load(FirstEntry); Load(SecondEntry); Epasop(WordFns[ICLOp]); FreeEntry(FirstEntry); FreeEntry(SecondEntry) end end end { DoICLStandardOp }; begin { load } with Entry^ do case Kind of Reference : if AccessKind = Bits then begin LoadAddress(Entry); Estklit(MCBytesPerWord); Eop(CVTII) end else begin CheckNeeded := (Entry^.RunError <> 0); if AccessKind = Bytes then AccessSize := ByteSize else AccessSize := DataSize(DataRep); if Indexed or (Class = FileRef) then begin LoadAddress(Entry); if Indexed then LoadAccess(AccessSize) else LoadBuffer(AccessSize) end else if AccessList <> nil then begin LoadAddress(AccessList); if Indirect then LoadIndirect; if Class = HeapRef then Epasop(CHKNEW2); AdjustLoad(Adjustment, AccessSize); FreeEntry(AccessList) end else if Indirect then begin AccessArea(BaseAddress, 0, MCBytesPerWord); if Class = PnterRef then Epasop(CHKNEW2); AdjustLoad(Adjustment, AccessSize) end else AccessArea(BaseAddress, Adjustment, AccessSize); if CheckNeeded then CheckLoadedValue(Entry) end; BlockRef : ; Address : ; AConstant : with TheConst do case Kind of IntValue, BoolValue, CharValue : Estklit(TheConst.Ival); RealValue : LoadReal(TheConst.Rval); StringValue, SetValue : LoadMultipleConst(TheConst); PntrValue : Estklit(0) end; Operation : case OpForm of Unary : DoUnaryOp; Binary : DoBinaryOp; Condition : DoBooleanOp; BlockCall : DoBlockCall; RangeChk : case CheckKind of SubrangeChecks : DoSubrangeChecks; WSubRangeChecks : DoWSubRangeChecks; TransferChecks : DoTransferChecks; WTransferChecks : DoWTransferChecks; MemberChecks : DoMembershipChecks end; ReadOp : DoReadOp; CAPSize : DoCAPSize; Stdrd : DoStandardOp; ICLStdrd : DoICLStandardOp end end; Entry^.Kind := Result end { load }; { 19.6 Saving and Reloading Values The procedure SaveValue is used to save a loaded expression result for subsequent re-use, in a temporary location acquired for the purpose, and to create a reference record for the temporary. The procedure LoadValue is used to reload a result saved in this way, or to load the value of a constant expression (which would not be saved). LoadValue does not alter the stack record describing the value to be loaded, so that multiple (re-) loading operations may be applied. } procedure SaveValue(ExpValue: StackEntry); visible; begin with ExpValue^ do begin Kind := Reference; Indirect := false; Class := VarRef; AccessList := nil; Acquire(MCBytesPerWord, Stack, BaseAddress); Adjustment := 0; AccessKind := Words; ByteSize := 0; Indexed := false; AddressArea(BaseAddress, 0, MCBytesPerWord); Eop(ESTORE) end end { savevalue }; procedure LoadValue(TempEntry: StackEntry); visible; begin with TempEntry^ do if Kind = AConstant then Estklit(TheConst.Ival) else if Indirect then begin AccessArea(BaseAddress, 0, MCBytesPerWord); AdjustLoad(Adjustment, MCBytesPerWord) end else AccessArea(BaseAddress, Adjustment, MCBytesPerWord) end { loadvalue }; begin { end of module } end.