-- file VirtCM.Mesa
-- edited by Schroeder, January 8, 1981 11:58 AM.
-- edited by Brotz, April 15, 1981 10:59 AM.

DIRECTORY
exD: FROM "ExceptionDefs",
gsD: FROM "GlobalStorageDefs"
USING [GetMemoryPages, ReturnMemoryPages],
InlineDefs USING [COPY],
ovD: FROM "OverviewDefs",
vmD: FROM "VirtualMgrDefs";

VirtCM: PROGRAM
IMPORTS exD, gsD, InlineDefs, vmD
EXPORTS vmD
SHARES vmD =

PUBLIC BEGIN

OPEN vmD;


MapCharIndexToPageByte: PROCEDURE [cm: ComposeMessagePtr,
index: ovD.CharIndex] RETURNS [PageNumber, CARDINAL] =
-- Get the page#, byte# pair for the index-th character of the compose message.
BEGIN
page: PageNumber;
byte: CARDINAL;
c: ovD.CharIndex ← 0;
FOR page IN [0 .. cm.filePageFF) DO
c ← c + cm.charMap[page].count; -- c is # of 1st chr off page.
IF c > index THEN EXIT;
REPEAT FINISHED => exD.SysBug[];
ENDLOOP;
byte ← index - (c - cm.charMap[page].count);
RETURN[page, byte];
END; -- of MapCharIndexToPageByte --


SetGetCacheForCMPage: PROCEDURE
[option: SetCacheOption, cm: ComposeMessagePtr, lpn: PageNumber,
index: ovD.CharIndex] RETURNS [erc: ovD.ErrorCode] =
-- If option is "new" then insert a new logical page at number lpn and set
-- g.first and g.free to index (the first character to be put in the page). If
-- option is "old" then get the logical page with number lpn into the page
-- cache and set the get cache to reference the contained characters.
-- ErrorCodes: cMTooBig ( possible on "new" only).
BEGIN
OPEN g: cm.get;
pn: PageNumber;
IF option = new THEN
BEGIN
[g.mtPtr, pn, erc] ← AllocateNewCMPage[cm, lpn];
IF erc # ovD.ok THEN
{VoidCharCache[@g]; -- Be tidy about dying -- RETURN[erc]};
END
ELSE [g.mtPtr, pn] ← GetMtPtr[cm, lpn, active];
g.first ← index;
g.free ← g.first + cm.charMap[pn].count;
g.floor ← 0;
g.string ← LOOPHOLE[g.mtPtr.address - 2, STRING];
RETURN[ovD.ok];
END; -- of SetGetCacheForCMPage.


InitComposeMessage: PROCEDURE [cMPtr: ComposeMessagePtr, s: STRING] =
-- The composeMessage is initialized to contain the string. All buffer pages are destroyed.
BEGIN
cMPtr.open ← TRUE;
VoidCharCache[@cMPtr.get];
cMPtr.textLength ← 0;
cMPtr.filePageFF ← 0;
cMPtr.inserting ← FALSE;
FOR p: MemoryTableEntryPtr ← cMPtr.memoryHeader, p.next UNTIL p = NIL DO
p.state ← unused;
IF p.address # NIL THEN -- return buffer pages if present
{gsD.ReturnMemoryPages[1, p.address]; p.address ← NIL};
ENDLOOP;
IF s # NIL THEN
BEGIN
StartMessageInsertion[cMPtr, 0];
IF InsertSubstringInMessage[cMPtr, s, 0, s.length] # ovD.ok THEN exD.SysBug[];
StopMessageInsertion[cMPtr];
END;
END; -- of InitComposeMessage --


PutMessageChar: PROCEDURE [cMPtr: ComposeMessagePtr, index: ovD.CharIndex,
char: CHARACTER] =
-- The character a position index is overwritten with char.
BEGIN
OPEN g: cMPtr.get;
erc: ovD.ErrorCode;
page: PageNumber;
byte: CARDINAL;
IF index ~IN [g.first .. g.free) THEN
BEGIN
[page, byte] ← MapCharIndexToPageByte[cMPtr, index];
erc ← SetGetCacheForCMPage[old, cMPtr, page, index- byte];
IF erc # ovD.ok THEN exD.SysBug[]; -- Can’t happen for "old".
END;
g.string[index + g.floor- g.first] ← char;
cMPtr.memoryHeader.state ← dirty;
END; -- of PutMessageChar --


ReplaceRangeInMessage: PROCEDURE [to, from: MessageRange]
RETURNS [erc: ovD.ErrorCode] =
-- The characters contained in the to range are overwritten with the characters contained in
-- the from range. to and from must be in different VMOs. to’s VMO must be a CM, and
-- from’s VMO can be a CM or a DM.
-- SysBugs: "Bad CharIndex", "to must be CM", "to = from".
-- ErrorCodes: cMTooBig [ Note: DeletesRange!!!].
BEGIN -- Quick & dirty implementation. [But it may be the best one. MDS]
WITH cM: to.message↑ SELECT FROM
CM => {DeleteRangeInMessage[to]; erc ← InsertRangeInMessage[to.start, @cM, from]};
ENDCASE => exD.SysBug[];
END; -- of ReplaceRangeInMessage --


InsertRangeInMessage: PROCEDURE [targetIndex: ovD.CharIndex,
targetMessage: ComposeMessagePtr, from: MessageRange]
RETURNS [erc: ovD.ErrorCode] =
-- The characters contained in the from range are inserted in the target message just before
-- the targetIndex character. targetMessage and from must be in different VMOs. The
-- former must be a CM, and the latter can be a CM or a DM.
-- SysBugs: "Bad CharIndex", "to must be CM", "to = from".
-- ErrorCodes: cMTooBig.
BEGIN
OPEN g: from.message.get; -- open the get cache of the from message
firstByteToCopy, copyCount: CARDINAL;
currentFromIndex: ovD.CharIndex;
erc ← ovD.ok;
IF targetMessage = from.message THEN exD.SysBug[];
StartMessageInsertion[targetMessage, targetIndex];
currentFromIndex ← from.start;
UNTIL currentFromIndex >= from.end DO
-- set the get cache of the from message for the currentFromIndex
[] ← GetMessageChar[from.message, currentFromIndex];
firstByteToCopy ← currentFromIndex + g.floor - g.first;
copyCount ← MIN[from.end - currentFromIndex, g.free - currentFromIndex];
erc ← InsertSubstringInMessage[targetMessage, g.string, firstByteToCopy, copyCount];
IF erc # ovD.ok THEN {AbandonMessageInsertion[targetMessage]; RETURN};
currentFromIndex ← currentFromIndex + copyCount;
ENDLOOP;
StopMessageInsertion[targetMessage];
END; -- of InsertRangeInMessage --


DeleteRangeInMessage: PROCEDURE [from: MessageRange] =
-- The characters in the range [from.start .. from.end) are deleted from msg.
-- WARNING: This procedure is very intricate! Be careful if you modify it!
BEGIN
erc: ovD.ErrorCode;
lpn: PageNumber;
bottomByte, topCount, index, holeSize: CARDINAL;
WITH cMO: from.message SELECT FROM
CM => BEGIN
OPEN g: cMO.get;
IF from.end > cMO.textLength OR from.start > from.end THEN exD.SysBug[];
IF (holeSize ← from.end - from.start) = 0 THEN RETURN; -- Null delete.
IF from.start IN [g.first .. g.free) THEN
{lpn ← g.mtPtr.logicalPageNumber; bottomByte ← from.start - g.first}
ELSE [lpn, bottomByte] ← MapCharIndexToPageByte[@cMO, from.start];
IF bottomByte # 0 AND holeSize >= (topCount ← cMO.charMap[lpn].count-bottomByte)
THEN BEGIN -- tail, but not all, of first page is to be removed
cMO.charMap[lpn].count ← cMO.charMap[lpn].count - topCount;
cMO.textLength ← cMO.textLength - topCount;
IF from.start < g.free THEN g.free ← g.free - topCount;
IF from.start <= g.first THEN g.first ← g.first - topCount;
IF (holeSize ← holeSize - topCount) = 0 THEN RETURN;
bottomByte ← 0;
lpn ← lpn + 1;
END;
UNTIL holeSize < (topCount ← cMO.charMap[lpn].count - bottomByte) DO
--remove whole pages
RemoveLP[@cMO, lpn];
IF (holeSize ← holeSize - topCount) = 0 THEN RETURN;
ENDLOOP;
-- if we get here then characters must be shifted down in the last page
IF from.start ~IN [g.first .. g.free) THEN
BEGIN
erc ← SetGetCacheForCMPage[old, @cMO, lpn, from.start - bottomByte];
IF erc # ovD.ok THEN exD.SysBug[]; -- Can’t happen for "old".
END;
FOR index IN [bottomByte + holeSize .. cMO.charMap[lpn].count) DO
g.string[index - holeSize] ← g.string[index];
ENDLOOP;
g.mtPtr.state ← dirty;
cMO.charMap[lpn].count ← (g.free ← g.free - holeSize) - g.first;
cMO.textLength ← cMO.textLength - holeSize;
END; --of CM case.
ENDCASE => exD.SysBug[];
END; -- of DeleteRangeInMessage --


AppendMessageChar: PROCEDURE [cM: ComposeMessagePtr, char: CHARACTER]
RETURNS [erc: ovD.ErrorCode] =
-- The character, char, is appended to the end of the msg.
--ErrorCodes: cMTooBig.
BEGIN
StartMessageInsertion[cM, cM.textLength];
erc ← InsertMessageChar[cM, char];
StopMessageInsertion[cM];
END; -- of AppendMessageChar --


UnAppendMessageChar: PROCEDURE [msgPtr: ComposeMessagePtr] =
-- This routine is used to process a rubout. It deletes the last character in the message.
BEGIN
DeleteRangeInMessage[MessageRange[msgPtr.textLength - 1, msgPtr.textLength, msgPtr]];
END; -- of UnAppendMessageChar --


StartMessageInsertion: PROCEDURE [cM: ComposeMessagePtr, where: ovD.CharIndex] =
-- Initializes a ComposeMessage for insertion just before the character "where". This
-- procedure must be called before the other insertion procedures, and eventually followed
-- by either StopMessageInsertion or AbandonMessageInsertion.
BEGIN
IF cM.inserting THEN exD.SysBug[];
IF where > cM.textLength THEN exD.SysBug[];
cM.inserting ← TRUE;
cM.insertionStart ← cM.insertionStop ← where;
END; -- of StartMessageInsertion --


InsertMessageChar: PROCEDURE [cM: ComposeMessagePtr, char: CHARACTER]
RETURNS [erc: ovD.ErrorCode] =
-- The character is appended to the current insertion.
-- SysBugs: "Insertion not in progress".
-- ErrorCodes: cMTooBig.
BEGIN
OPEN g: cM.get;
erc ← ovD.ok; -- Assume the best.
IF ~cM.inserting THEN exD.SysBug[];
IF cM.insertionStop # g.free OR g.free >= g.first + cMOMaxCharPerPage THEN
{IF (erc ← SetGetCacheForInserting[cM]) # ovD.ok THEN RETURN};
g.string[g.free - g.first] ← char;
cM.textLength ← cM.textLength + 1;
cM.charMap[g.mtPtr.logicalPageNumber].count ← (g.free ← g.free + 1) - g.first;
g.mtPtr.state ← dirty;
cM.insertionStop ← cM.insertionStop + 1;
END; -- of InsertMessageChar --


InsertSubstringInMessage: PROCEDURE [cM: ComposeMessagePtr, source: STRING,
first: CARDINAL, charsToCopy: CARDINAL] RETURNS [erc: ovD.ErrorCode] =
-- source[first .. first+charsToCopy) are inserted in the cM at the current insertion point.
-- source.length and surce.maxlength are not referenced.
BEGIN
OPEN g: cM.get;
count, index, firstFreeByte: CARDINAL;
IF ~cM.inserting THEN exD.SysBug[];
erc ← ovD.ok;
WHILE charsToCopy > 0 DO
erc ← SetGetCacheForInserting[cM];
IF erc # ovD.ok THEN RETURN;
firstFreeByte ← g.free - g.first;
count ← MIN[charsToCopy, cMOMaxCharPerPage - firstFreeByte];
FOR index IN [0 .. count) DO
g.string[firstFreeByte + index] ← source[first + index];
ENDLOOP;
g.mtPtr.state ← dirty;
cM.textLength ← cM.textLength + count;
cM.charMap[g.mtPtr.logicalPageNumber].count ← firstFreeByte + count;
cM.insertionStop ← cM.insertionStop + count;
g.free ← g.free + count;
first ← first + count;
charsToCopy ← charsToCopy - count;
ENDLOOP;
END; -- of InsertSubstringInMessage --


SetGetCacheForInserting: PRIVATE PROCEDURE [cM: ComposeMessagePtr]
RETURNS [erc: ovD.ErrorCode] =
-- Arranges the Get Cache to locate the page on which the insertion is to take place, and
-- makes sure that the insertion point is g.free.
-- ErrorCodes: cMTooBig.
BEGIN
OPEN g: cM.get;
page: PageNumber; byte: CARDINAL;

-- internal procedure

BifurcateMessage: PROCEDURE RETURNS [erc: ovD.ErrorCode] =
-- Force a page break between char cM.insertionStop-1 & cM.insertionStop. page and byte
-- are the logical page number and offset corresponding to ndx. The customer is
-- presumed to have checked that cM.insertionStop - 1 is not already at the end of a
-- page and that cM.insertionStop # 0. Assumes that cache has at least 2 pages in it.
-- Sets get cache to logical page of cM.insertionStop-1.
-- WARNING: DON’T FOOL AROUND WITH THIS PROCEDURE UNLESS YOU KNOW
-- WHAT YOU ARE DOING!
-- ErrorCodes: cMTooBig.
BEGIN
ndx: ovD.CharIndex = cM.insertionStop;
copyCount, copyStart, fromCount, cx: CARDINAL;
fromPage: PageNumber;
toString: STRING;
toMtPtr: MemoryTableEntryPtr;

copyCount ← cM.charMap[page].count - byte; -- size of the tail to be moved
--make a new page to copy tail onto
erc ← SetGetCacheForCMPage[new, cM, page + 1, ndx];
IF erc # ovD.ok THEN RETURN; -- Oops.
toMtPtr ← g.mtPtr; --remember where the buffer for the new page is
g.mtPtr.state ← dirty; -- we’re going to copy into this page
toString ← g.string; -- save this string for copying later
fromPage ← g.mtPtr.logicalPageNumber - 1;
fromCount ← cM.charMap↑[fromPage].count; -- # of chars stored on from page now
cM.memoryHeader ← toMtPtr.next; --remove new page from the buffer pool
erc ← SetGetCacheForCMPage[old, cM, fromPage, ndx - (fromCount - copyCount)];
IF erc # ovD.ok THEN exD.SysBug[]; -- Can’t happen for "old".
toMtPtr.next ← g.mtPtr.next; -- put new page back into the buffer pool
g.mtPtr.next ← toMtPtr;
fromPage ← g.mtPtr.logicalPageNumber; --adjust page numbers for possible compaction
toMtPtr.logicalPageNumber ← fromPage + 1;
copyStart ← fromCount - copyCount;
FOR cx IN [0 .. copyCount) DO
toString[cx] ← g.string[copyStart + cx];
ENDLOOP;
g.free ← g.free - copyCount;
cM.charMap[fromPage].count ← copyStart;
cM.charMap[fromPage + 1].count ← copyCount;
END; -- of BifurcateMessage --

-- start code
DO --may have to do twice if cM is to be compacted
BEGIN -- for EXITs
erc ← ovD.ok; -- Assume the best.
IF cM.insertionStop = 0 THEN GOTO GetFirstPage;
IF cM.insertionStop - 1 IN [g.first .. g.free) THEN
BEGIN
IF g.free = cM.insertionStop THEN
BEGIN
IF g.free < g.first + cMOMaxCharPerPage THEN GOTO AllSet
ELSE {page ← g.mtPtr.logicalPageNumber; GOTO GetNewPage}
END
ELSE BEGIN
page ← g.mtPtr.logicalPageNumber; byte ← cM.insertionStop - g.first;
GOTO BifurcatePage;
END;
END;
[page, byte] ← MapCharIndexToPageByte[cM, cM.insertionStop - 1];
byte ← byte + 1; -- up to place for the new character
IF byte < cM.charMap[page].count THEN GOTO BifurcatePage;
IF byte = cMOMaxCharPerPage THEN GOTO GetNewPage;
GOTO GetOldPage;

EXITS
GetFirstPage => erc ← SetGetCacheForCMPage[new, cM, 0, 0];
GetNewPage =>
erc ← SetGetCacheForCMPage[new, cM, page + 1, cM.insertionStop];
GetOldPage =>
erc ← SetGetCacheForCMPage[old, cM, page, cM.insertionStop - byte];
BifurcatePage => erc←BifurcateMessage[];
AllSet => NULL; -- to get out of the mess above
END; -- of exits block

IF erc=ovD.cMTooBig AND CompactCM[cM] = ovD.ok THEN LOOP;
EXIT;
ENDLOOP;
END; -- of SetGetCacheForInserting --


UnInsertMessageChar: PROCEDURE [cM: ComposeMessagePtr] =
-- This routine is used to process a rubout. It deletes the last character in an insertion, and
-- is a nop if the insertion is empty.
BEGIN
OPEN g: cM.get;
IF ~cM.inserting THEN exD.SysBug[];
IF cM.insertionStop = cM.insertionStart THEN RETURN;
DeleteRangeInMessage[MessageRange
[start: cM.insertionStop - 1, end: cM.insertionStop, message: cM]];
cM.insertionStop ← cM.insertionStop - 1;
END; -- UnInsertMessageChar --


StopMessageInsertion: PROCEDURE [cM: ComposeMessagePtr] =
-- The current insertion is terminated, and the inserted characters become part of the
-- message.
BEGIN
IF ~cM.inserting THEN exD.SysBug[] ELSE cM.inserting ← FALSE;
END; -- of StopMessageInsertion --


AbandonMessageInsertion: PROCEDURE [cM: ComposeMessagePtr] =
-- The current insertion is discarded, and the inserted characters go away.
BEGIN --Simple implementation.
range: MessageRange;
range ← [cM.insertionStart, cM.insertionStop, cM]; -- Save over StopMessageInsertion call.
StopMessageInsertion[cM];
DeleteRangeInMessage[range];
END; -- of AbandonMessageInsertion --


AllocateNewCMPage: PRIVATE PROCEDURE [cM: ComposeMessagePtr, lpn: PageNumber]
RETURNS [MemoryTableEntryPtr,PageNumber, ovD.ErrorCode] =
-- Reuses last logical page in the file if its count is zero; otherwise allocates a new logical
-- page and file page. Returns pointer to mte containing new page and the (possibly
-- different) logical page number of the new page.
-- ErrorCodes: cMTooBig.
-- WARNING: THIS PROCEDURE MAY CHANGE THE MEANING OF LPN’s AND MTPTR’s
BEGIN
filePage, pg: PageNumber;
mtPtr: MemoryTableEntryPtr;
IF cM.filePageFF < lpn THEN exD.SysBug[];
IF cM.filePageFF > 0 AND cM.charMap[cM.filePageFF - 1].count = 0
THEN filePage ← cM.charMap[cM.filePageFF - 1].page -- reuse an old file page
ELSE BEGIN
-- need a new file page
IF cM.filePageFF = cMOCharMapTableSize THEN RETURN[NIL, 0, ovD.cMTooBig];
filePage ← cM.filePageFF;
cM.filePageFF ← cM.filePageFF + 1;
END;
FOR pg DECREASING IN (lpn .. cM.filePageFF) DO -- Adjust charMap.
cM.charMap[pg] ← cM.charMap[pg-1];
ENDLOOP;
cM.charMap[lpn] ← [count: 0, page: filePage]; -- create entry for new LP
FOR mtPtr ← cM.memoryHeader, mtPtr ← mtPtr.next UNTIL mtPtr = NIL DO
IF mtPtr.logicalPageNumber >= lpn THEN
mtPtr.logicalPageNumber ← mtPtr.logicalPageNumber + 1;
ENDLOOP;
[mtPtr, pg] ← GetMtPtr[cM, lpn, new];
RETURN[mtPtr, pg, ovD.ok];
END; -- of AllocateNewCMPage --


TryToCompactBufferPool: PROCEDURE [cmp: ComposeMessagePtr]
RETURNS [BOOLEAN, PageNumber] =
-- Tries to compact the pages in the designated CM’s buffer pool to create an empty buffer.
-- Returns TRUE if the compaction succeeds, otherwise FALSE. When compaction succeeds
-- the emptied page is removed from the CM, the PageNumber returns the number of the
-- removed page, and the associated Mte is marked unused. This procedure assumes that
-- there are no unused buffers in the pool to start with.
BEGIN
mtptr1, mtptr2, mtptr3: MemoryTableEntryPtr;
lpn1, lpn2, lpn3: PageNumber;
toIndex, fromIndex: CARDINAL;
s1, s2: STRING;
FOR mtptr1 ← cmp.memoryHeader, mtptr1.next UNTIL mtptr1 = NIL DO
FOR mtptr2 ← mtptr1.next, mtptr2.next UNTIL mtptr2 = NIL DO
lpn1 ← mtptr1.logicalPageNumber;
lpn2 ← mtptr2.logicalPageNumber;
IF (lpn2 = lpn1 + 1 OR lpn1 = lpn2 + 1) AND
cmp.charMap[lpn1].count + cmp.charMap[lpn2].count <= cMOMaxCharPerPage
THEN BEGIN -- compact these two pages
IF lpn1 > lpn2 THEN --make sure 1 is smaller than 2
BEGIN
lpn3 ← lpn2; lpn2 ← lpn1; lpn1 ← lpn3;
mtptr3 ← mtptr2; mtptr2 ← mtptr1; mtptr1 ← mtptr3;
END;
-- Now mush 2 into 1 and remove 2.
toIndex ← cmp.charMap[lpn1].count;
s1 ← LOOPHOLE[mtptr1.address - 2, STRING];
s2 ← LOOPHOLE[mtptr2.address - 2, STRING];
FOR fromIndex IN [0 .. cmp.charMap[lpn2].count) DO
s1[toIndex + fromIndex] ← s2[fromIndex];
ENDLOOP;
cmp.charMap[lpn1].count ← toIndex + cmp.charMap[lpn2].count;
mtptr1.state ← dirty;
mtptr2.state ← unused;
cmp.charMap[lpn2].count ← 0;
RemoveLP[cmp, lpn2];
RETURN[TRUE, lpn2];
END;
ENDLOOP;
ENDLOOP;
RETURN[FALSE, 0]; -- the attempt to compact failed
END; -- of TryToCompactBufferPool --


CompactCM: PRIVATE PROCEDURE [cM: ComposeMessagePtr]
RETURNS [ovD.ErrorCode] =
-- Compacts the cm.
-- WARNING: THIS PROCEDURE CHANGES THE MEANING OF LPN’s
BEGIN OPEN g: cM↑.get;
buffer: POINTER = gsD.GetMemoryPages[1];
bufferS: STRING = LOOPHOLE[buffer-2, STRING];
count: CARDINAL;
place: CARDINAL ← 0;
savedInsertionStart, savedInsertionStop: CARDINAL;
savedInserting: BOOLEAN ← cM.inserting;
IF cM.textLength
> cMOMaxCharPerPage * CARDINAL[cMOCharMapTableSize - 1] THEN
RETURN[ovD.cMTooBig];
IF savedInserting THEN BEGIN
savedInsertionStart ← cM.insertionStart;
savedInsertionStop ← cM.insertionStop;
cM.inserting ← FALSE;
END;
StartMessageInsertion[cM, 0];
UNTIL place >= cM↑.textLength DO
[] ← GetMessageChar[cM, place];
count ← g.free - g.first;
InlineDefs.COPY[@g.string.text, (count + 1) / 2, buffer];
RemoveLP[cM, g.mtPtr.logicalPageNumber];
[] ← InsertSubstringInMessage[cM, bufferS, 0, count];
place ← place + count;
ENDLOOP;
StopMessageInsertion[cM];
IF savedInserting THEN BEGIN
cM.insertionStart ← savedInsertionStart;
cM.insertionStop ← savedInsertionStop;
cM.inserting ← TRUE;
END;
gsD.ReturnMemoryPages[1,buffer];
RETURN[ovD.ok];
END; -- of CompactCM --


RemoveLP: PRIVATE PROCEDURE [cM: ComposeMessagePtr, lpn: PageNumber] =
-- removes designated LP from within file and places it at end for possible later reuse.
-- WARNING: THIS PROCEDURE CHANGES THE MEANING OF LPN’s
BEGIN
filePage, pg: PageNumber;
mtPtr: MemoryTableEntryPtr;
IF lpn >= cM.filePageFF THEN exD.SysBug[];
IF lpn = cM.get.mtPtr.logicalPageNumber THEN VoidCharCache[@cM.get];
cM.textLength ← cM.textLength - cM.charMap[lpn].count;
filePage ← cM.charMap[lpn].page;
FOR pg IN (lpn .. cM.filePageFF) DO
cM.charMap[pg - 1] ← cM.charMap[pg];
ENDLOOP;
cM.charMap[cM.filePageFF - 1] ← [count: 0, page: filePage];
FOR mtPtr ← cM.memoryHeader, mtPtr ← mtPtr.next UNTIL mtPtr = NIL DO
SELECT mtPtr.logicalPageNumber FROM
> lpn => mtPtr.logicalPageNumber ← mtPtr.logicalPageNumber - 1;
= lpn => mtPtr.state ← unused;
ENDCASE => NULL;
ENDLOOP;
END; -- of RemoveLP --


MapVirtualToComposeMessage: PROCEDURE [vmp: VirtualMessagePtr]
RETURNS [cmp: ComposeMessagePtr] =
-- Loopholes vmp to cmp. Calls SysBug if vmp was not a ComposeMessagePtr.
BEGIN
WITH cm: vmp SELECT FROM
CM => RETURN[@cm];
ENDCASE => exD.SysBug[];
END; -- of MapVirtualToComposeMessage --


END. -- of VirtCM --