DIRECTORY
Basics USING [UnsafeBlock],
BasicTime USING [GMT, Now, nullGMT, Period, Update],
Camelot USING [btidT, tidT],
IO USING [EndOfStream, GetChar, GetLength, STREAM, UnsafeGetBlock],
PBasics USING [charsPerWord],
Process USING [Detach, MsecToTicks, Pause, SetTimeout, Ticks],
RedBlackTree USING [Compare, Create, Delete, GetKey, Insert, InsertNode, Lookup, LookupNextLarger, LookupSmallest, Node, Size, Table, UserData],
RefText USING [ObtainScratch, ReleaseScratch],
Rope USING [Concat, Compare, FromRefText, ROPE],
YggDID USING [DID],
YggDIDPrivate USING [DIDRep],
YggDIDMap USING [GetComponentFiles, OpenDocumentFromDID],
YggEnvironment USING [AccessRights, LockMode, LockOption, nullTransID, TransID],
YggFileStream USING [StreamFromComponentFilesAndTid],
YggFixedNames USING [Contents, Inlinks, Outlinks],
YggInternal USING [Document, FileHandle],
YggLock USING [Failed, MakeLockID, Set],
YggMonitoringLog USING [LockConflictInfo, notice],
YggRep USING [AccurateGMT, AccurateGMTRep, AccurateGMTRepByteSize, Attribute, AttributePreambleByte, AttributeValue, Bits, BitsFromBits, BitsRep, date, float, did, int, metaAttributeMod, rope, shortRope, TypedPrimitiveElement, unknown, uninterpretedBytes, VDoc, VDocRep],
YggTransaction USING [EqualTrans, GetParent, IsNullTrans, NotePossibleDocumentUpdate],
YggVolatileObjectCache;
Exported conversion procedures
VolatizeFromDID:
PUBLIC
PROC [transID: YggEnvironment.TransID, did: YggDID.
DID,
access: YggEnvironment.AccessRights, lock: YggEnvironment.LockOption, metaAttributesOnly:
BOOL]
RETURNS [vDoc: YggRep.VDoc ←
NIL] ~ {
Given a DID, return the volatile form of the document it refers to. If metaAttributesOnly is TRUE, then the transID must be null.
parseAttributes:
PROC [attrStream:
IO.
STREAM]
RETURNS [attributeList: LIST OF YggRep.Attribute ← NIL, contentsAttribute: YggRep.TypedPrimitiveElement ← [YggRep.unknown,
NIL], outlinksAttribute:
LIST
OF YggRep.AttributeValue ← NIL, inlinksAttribute:
LIST
OF YggRep.AttributeValue ← NIL] = {
readInt:
PROC
RETURNS [int:
INT] = {
read an int from the attributes stream
charsRead: INT ← 0;
rint: REF INT;
rint ← NEW[INT];
TRUSTED {charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[rint], 0, BYTES[INT]]];};
IF charsRead # BYTES[INT] THEN ERROR;
RETURN[rint^];
};
readString:
PROC [extraChars:
INT]
RETURNS [string:
ROPE ←
NIL]= {
read a null terminated string from the attributes stream
nullFound: BOOL ← FALSE;
lenInScratch: INT ← 0;
numberToFetch: INT ← PBasics.charsPerWord-extraChars;
fourChars: REF PACKED ARRAY [0..PBasics.charsPerWord) OF CHAR;
scratch: REF TEXT = RefText.ObtainScratch[scratchBuffSize];
fourChars ← NEW[PACKED ARRAY [0..PBasics.charsPerWord) OF CHAR];
UNTIL nullFound
DO
charsRead: INT ← 0;
TRUSTED {charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[fourChars], 0 , numberToFetch]];};
IF charsRead # numberToFetch THEN ERROR;
FOR charNo:
INT
IN [0..numberToFetch)
DO
IF fourChars[charNo] = 0C THEN {nullFound ← TRUE; EXIT};
scratch[lenInScratch] ← fourChars[charNo];
lenInScratch ← lenInScratch + 1;
IF lenInScratch = scratchBuffSize
THEN {
scratch.length ← lenInScratch;
string ← Rope.Concat[string, Rope.FromRefText[s: scratch, start: 0, len: lenInScratch]];
lenInScratch ← 0;
};
ENDLOOP;
numberToFetch ← PBasics.charsPerWord;
ENDLOOP;
IF lenInScratch # 0
THEN {
scratch.length ← lenInScratch;
string ← Rope.Concat[string, Rope.FromRefText[s: scratch, start: 0, len: lenInScratch]];
};
RefText.ReleaseScratch[scratch];
};
doneWithAttributes: BOOL ← FALSE;
attributeListLast: LIST OF YggRep.Attribute ← NIL;
contentsDocType ← readInt[];
DO
-- for each attribute
attributeName: ROPE ← NIL; -- attribute name
attributeValue: LIST OF YggRep.AttributeValue ← NIL; -- attribute name
attributeValueLast: LIST OF YggRep.AttributeValue ← NIL; -- attribute name
numberOfAttributeValues: INT ← 1;
preampleByte: CHAR;
preample: YggRep.AttributePreambleByte;
fieldDocType: CARD;
TRUSTED {preampleByte ←
IO.GetChar[attrStream !
IO.EndOfStream => {
doneWithAttributes ← TRUE;
CONTINUE;
};
];}; -- @preample points to preample[0]
IF doneWithAttributes THEN EXIT;
preample ← LOOPHOLE[preampleByte];
fieldDocType ←
SELECT preample.typeCode
FROM
integer => YggRep.int,
ropeLarge => YggRep.rope,
ropeShort => YggRep.shortRope,
float => YggRep.float,
date => YggRep.date,
did => YggRep.did,
uninterpretedBytes => YggRep.uninterpretedBytes,
ENDCASE => YggRep.unknown;
attributeName ← readString[1]; -- read attribute name
IF ~preample.singletonAttribute
THEN {
numberOfAttributeValues ← readInt[];
};
FOR attVal:
INT
IN [0..numberOfAttributeValues)
DO
-- for each attribute value (a field)
fieldName: ROPE ← NIL;
valueSet: LIST OF YggRep.TypedPrimitiveElement ← NIL; -- set of values for field
valueSetLast: LIST OF YggRep.TypedPrimitiveElement ← NIL; -- set of values for field
IF ~preample.noFieldNames
THEN {
fieldName ← readString[0]; -- read field name
};
DO
-- for each typed primitive element in the field's value set
fieldValue: YggRep.Bits;
IF preample.typeCode = separate
THEN {
fieldDocType ← readInt[];
};
SELECT fieldDocType
FROM
YggRep.unknown => EXIT;
YggRep.int => {
i: INT32;
ri: REF INT32;
i ← readInt[];
ri ← NEW[INT32 ← i];
fieldValue ← ri;
};
YggRep.shortRope => {
rRope: ROPE;
rRope ← readString[0];
fieldValue ← rRope;
};
YggRep.rope => {
len: INT;
lenToRead: INT;
charsRead: INT;
rRope: ROPE;
scratch: REF TEXT;
len ← readInt[];
lenToRead ← PBasics.charsPerWord * ((len - 1 + PBasics.charsPerWord)/PBasics.charsPerWord);
scratch ← RefText.ObtainScratch[lenToRead];
TRUSTED {charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[scratch, LONG POINTER]+UNITS[TEXT[0]], 0 , lenToRead]];};
IF charsRead # lenToRead THEN ERROR;
scratch.length ← len;
rRope ← Rope.FromRefText[s: scratch, start: 0, len: len];
fieldValue ← rRope;
};
YggRep.float => {
rReal: REF REAL32;
rReal ← NEW[REAL32];
TRUSTED {
charsRead: INT;
ptReal: LONG POINTER TO REAL32;
ptReal ← LOOPHOLE[rReal];
charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[ptReal], 0, BYTES[REAL32]]];
IF charsRead # BYTES[REAL32] THEN ERROR;
};
fieldValue ← rReal;
};
YggRep.date => {
rAccurateGMT: YggRep.AccurateGMT;
rAccurateGMT ← NEW[YggRep.AccurateGMTRep];
TRUSTED {
charsRead: INT;
ptAGMT: LONG POINTER TO YggRep.AccurateGMTRep;
ptAGMT ← LOOPHOLE[rAccurateGMT];
charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[ptAGMT], 0, YggRep.AccurateGMTRepByteSize]];
IF charsRead # YggRep.AccurateGMTRepByteSize THEN ERROR;
};
fieldValue ← rAccurateGMT;
};
YggRep.did => {
rDID: DID;
rDID ← NEW[DIDRep];
TRUSTED {
charsRead: INT;
ptDID: LONG POINTER TO DIDRep;
ptDID ← LOOPHOLE[rDID];
charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[ptDID], 0, BYTES[DIDRep]]];
IF charsRead # BYTES[DIDRep] THEN ERROR;
};
fieldValue ← rDID;
};
ENDCASE => {
charsRead: INT;
junk: REF PACKED ARRAY [0..PBasics.charsPerWord) OF CHAR;
len: INT;
lenToRead: INT;
nullsToRead: INT;
rBits: REF YggRep.BitsRep;
len ← readInt[];
lenToRead ← PBasics.charsPerWord * ((len - 1 + PBasics.charsPerWord)/PBasics.charsPerWord);
rBits ← NEW[YggRep.BitsRep[len]];
rBits.validBytes ← len;
TRUSTED {
ptBits: LONG POINTER TO YggRep.BitsRep;
ptBits ← LOOPHOLE[rBits];
charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[ptBits, LONG POINTER] + UNITS[YggRep.BitsRep[0]], 0, len]];
IF charsRead # len THEN ERROR;
};
nullsToRead ← lenToRead - len;
IF nullsToRead > 0
THEN
TRUSTED {
junk ← NEW[PACKED ARRAY [0..PBasics.charsPerWord) OF CHAR];
charsRead ← IO.UnsafeGetBlock[attrStream, [LOOPHOLE[junk], 0 , nullsToRead]];
IF charsRead # nullsToRead THEN ERROR;
};
fieldValue ← rBits;
};
IF valueSet = NIL THEN valueSetLast ← valueSet ← CONS[[fieldDocType, fieldValue], NIL]
ELSE valueSetLast ← (valueSetLast.rest ← CONS[[fieldDocType, fieldValue], NIL]);
IF preample.singletonField THEN EXIT;
ENDLOOP; -- for each typed primitive element in the field's value set
IF attributeValue = NIL THEN attributeValueLast ← attributeValue ← CONS[[fieldName, valueSet], NIL]
ELSE attributeValueLast ← (attributeValueLast.rest ← CONS[[fieldName, valueSet], NIL]);
ENDLOOP; -- for each attribute value
SELECT
TRUE
FROM
Rope.Compare[YggFixedNames.Contents, attributeName,
FALSE] = equal => {
Check to be sure that the value is a singleton value of a singleton set
IF attributeValue = NIL THEN ERROR;
IF attributeValue.first.valueSet = NIL THEN ERROR;
IF attributeValue.rest # NIL THEN ERROR;
IF attributeValue.first.valueSet = NIL THEN ERROR;
IF attributeValue.first.valueSet.rest # NIL THEN ERROR;
contentsAttribute ← attributeValue.first.valueSet.first;
};
Rope.Compare[YggFixedNames.Outlinks, attributeName,
FALSE] = equal
=> {
Make sure the list of links is all to DID's, and build up the outlinks value
FOR linkList:
LIST
OF YggRep.AttributeValue ← attributeValue, linkList.rest
UNTIL linkList =
NIL
DO
FOR vS:
LIST
OF YggRep.TypedPrimitiveElement ← linkList.first.valueSet, vS.rest
UNTIL vS =
NIL
DO
IF vS.first.docType # YggRep.did THEN ERROR;
ENDLOOP;
ENDLOOP;
outlinksAttribute ← attributeValue;
};
Rope.Compare[YggFixedNames.Inlinks, attributeName,
FALSE] = equal
=> {
Make sure the list of links is all to DID's, and build up the inlinks value
FOR linkList:
LIST
OF YggRep.AttributeValue ← attributeValue, linkList.rest
UNTIL linkList =
NIL
DO
FOR vS:
LIST
OF YggRep.TypedPrimitiveElement ← linkList.first.valueSet, vS.rest
UNTIL vS =
NIL
DO
IF vS.first.docType # YggRep.did THEN ERROR;
ENDLOOP;
ENDLOOP;
inlinksAttribute ← attributeValue;
};
ENDCASE => {
IF attributeList = NIL THEN attributeListLast ← attributeList ← CONS[[attributeName, preample.ordered, attributeValue], NIL]
ELSE attributeListLast ← (attributeListLast.rest ← CONS[[attributeName, preample.ordered, attributeValue], NIL]);
};
ENDLOOP; -- for each attribute
};
contents, attributes, meta: IO.STREAM ← NIL;
contentsDocType: INT ← -1;
doc: YggInternal.Document ← NIL;
componentFiles: LIST OF YggInternal.FileHandle;
IF ~metaAttributesOnly
THEN {
[] ← YggLock.Set[
trans: transID,
lock: YggLock.MakeLockID[did],
mode: lock.mode,
wait: lock.ifConflict=wait
! YggLock.Failed => {
-- Log the error and let the error propagate.
logProc: PROC [YggMonitoringLog.LockConflictInfo];
IF (logProc ← YggMonitoringLog.notice.lockConflict) #
NIL
THEN
logProc[[
what: why, -- (conflict or timeout)
where: "YggVolatilizeImpl.VolatizeFromDID",
transID: transID,
mode: lock.mode,
specifics: entireFile[""],
message: ""
]]
}
];
};
IF (vDoc ← LookupDIDInCache[did, transID, lock.mode]) # NIL THEN RETURN;
ReserveDIDInCache[did, transID];
doc ← YggDIDMap.OpenDocumentFromDID[did, transID];
componentFiles ← YggDIDMap.GetComponentFiles[doc];
contents ← YggFileStream.StreamFromComponentFilesAndTid[componentFiles: componentFiles, fileUse: $contents, tid: transID];
IF contents # NIL THEN {
IF IO.GetLength[contents] <= 0 THEN SIGNAL itsZero;
};
attributes ← YggFileStream.StreamFromComponentFilesAndTid[componentFiles: componentFiles, fileUse: $attributes, tid: transID];
IF attributes #
NIL
THEN {
IF IO.GetLength[attributes] <= 0 THEN SIGNAL itsZero;
};
meta ← YggFileStream.StreamFromComponentFilesAndTid[componentFiles: componentFiles, fileUse: $meta, tid: transID];
vDoc ← NEW[YggRep.VDocRep];
vDoc.did ← did;
vDoc.tid ← IF lock.mode = read THEN YggEnvironment.nullTransID ELSE transID;
IF attributes #
NIL
THEN {
attributeList: LIST OF YggRep.Attribute ← NIL;
contentsAttribute: YggRep.TypedPrimitiveElement ← [YggRep.unknown, NIL];
outlinksAttribute: LIST OF YggRep.AttributeValue ← NIL;
inlinksAttribute: LIST OF YggRep.AttributeValue ← NIL;
[attributeList, contentsAttribute, outlinksAttribute, inlinksAttribute] ← parseAttributes[attributes];
IF contentsAttribute # [YggRep.unknown,
NIL]
THEN {
IF contents # NIL THEN ERROR;
vDoc.contents ← contentsAttribute;
};
vDoc.attributes ← attributeList;
vDoc.outlinks ← outlinksAttribute;
vDoc.inlinks ← inlinksAttribute;
};
IF meta #
NIL
THEN {
attributeList: LIST OF YggRep.Attribute ← NIL;
contentsAttribute: YggRep.TypedPrimitiveElement ← [YggRep.unknown, NIL];
[attributeList, contentsAttribute] ← parseAttributes[meta];
IF contentsAttribute # [YggRep.unknown, NIL] THEN ERROR;
vDoc.metaAttributes ← attributeList;
};
IF contents #
NIL
THEN {
bits: REF YggRep.BitsRep;
size: INT;
bytesLeft: INT;
nextByteToRead: INT ← 0;
IF contentsDocType = -1 THEN ERROR;
vDoc.contents.docType ← contentsDocType;
size ← bytesLeft ← IO.GetLength[contents];
IF size <= 0 THEN SIGNAL itsZero;
vDoc.contents.bits ← bits ← NEW[YggRep.BitsRep[size]];
bits.validBytes ← size;
WHILE bytesLeft > 0
DO
nBytesRead: INT;
unsafeBlock: Basics.UnsafeBlock;
TRUSTED {
firstByte: LONG POINTER;
firstByte ← LOOPHOLE[vDoc.contents.bits, LONG POINTER] + UNITS[YggRep.BitsRep[0]];
unsafeBlock ← [LOOPHOLE[firstByte], nextByteToRead, bytesLeft];
nBytesRead ← IO.UnsafeGetBlock[self: contents, block: unsafeBlock];
};
bytesLeft ← bytesLeft - nBytesRead;
nextByteToRead ← nextByteToRead + nBytesRead;
ENDLOOP;
};
IF lock.mode # read THEN YggTransaction.NotePossibleDocumentUpdate[transID, vDoc];
IF vDoc.contents.docType # YggRep.unknown AND vDoc.contents.bits = NIL THEN SIGNAL itsZero;
CacheDID[did, transID, vDoc];
Cache management utilities
LatchVDoc:
PUBLIC
ENTRY
PROC [vDoc: YggRep.VDoc, wait:
BOOL ←
TRUE]
RETURNS [latched:
BOOL ← TRUE] ~ {
Set a short term latch.
ENABLE UNWIND => {};
IF vDoc = NIL THEN RETURN[FALSE];
WHILE vDoc.latched
DO
IF ~wait THEN RETURN[FALSE];
WAIT latchCondition;
ENDLOOP;
vDoc.latched ← TRUE;
};
UnlatchVDoc:
PUBLIC
ENTRY
PROC [vDoc: YggRep.VDoc]
RETURNS [latched:
BOOL ←
FALSE] ~ {
Remove a short term latch.
ENABLE UNWIND => {};
IF vDoc.latched THEN {vDoc.latched ← FALSE; RETURN [TRUE]};
BROADCAST latchCondition;
};
scratchVDocUnderMonitor: YggRep.VDoc ← NEW[YggRep.VDocRep];
LookupDIDInCache:
PUBLIC
ENTRY
PROC [did:
DID, transID: YggEnvironment.TransID, mode: YggEnvironment.LockMode]
RETURNS [vDoc: YggRep.VDoc ←
NIL] ~ {
Given a DID, transaction, and lock mode, return the volatile form of the document if it is cached. If the object is reserved, block until this is over.
For readers, the VDoc for this transaction or the nearest parent transaction is returned (or for the null transaction).
For writers, the cached VDoc must match both the did and tid. If any object with the proper did exists, a new object is constructed with the did and tid from a deep copy of the nearest parent transaction. Otherwise, NIL is returned.
ENABLE UNWIND => {};
val: REF;
tid: Camelot.tidT ← transID;
DO
transFound: BOOL ← FALSE;
scratchVDocUnderMonitor.did ← did; -- do this every time due to the WAIT below
scratchVDocUnderMonitor.tid ← tid;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
last: LIST OF YggRep.Attribute;
vDoc: YggRep.VDoc ← NIL;
entry ← NARROW[val];
entry.timeOfLastVolatize ← Now;
IF entry.users # 0 THEN {WAIT myCondition; LOOP;};
IF mode = read THEN RETURN[entry.vDoc];
IF YggTransaction.EqualTrans[tid, transID]
THEN
{
IF mode # read THEN YggTransaction.NotePossibleDocumentUpdate[transID, vDoc];
RETURN[entry.vDoc];
};
vDoc ←
NEW[YggRep.VDocRep ← [
did: did,
tid: transID,
contents: [YggRep.unknown, NIL],
contentsChanged: FALSE,
attributes: NIL, -- the attributes of the document
attributesChanged: NIL
FOR aL:
LIST
OF YggRep.Attribute ← entry.vDoc.attributes, aL.rest
UNTIL aL =
NIL
DO
IF vDoc.attributes = NIL THEN last ← vDoc.attributes ← LIST[aL.first]
ELSE {last.rest ← LIST[aL.first]; last ← last.rest; };
ENDLOOP;
vDoc.contents.docType ← entry.vDoc.contents.docType;
SELECT vDoc.contents.docType FROM
YggRep.unknown => ERROR;
YggRep.int => vDoc.contents.bits ← NEW[INT ← NARROW[entry.vDoc.contents.bits, REF INT]^];
YggRep.shortRope, YggRep.rope, YggRep.did => vDoc.contents.bits ← entry.vDoc.contents.bits;
YggRep.float => vDoc.contents.bits ← NEW[REAL32 ← NARROW[entry.vDoc.contents.bits, REF REAL32]^];
YggRep.date => vDoc.contents.bits ← NEW[YggRep.AccurateGMTRep ← NARROW[entry.vDoc.contents.bits, REF YggRep.AccurateGMTRep]^];
ENDCASE => vDoc.contents.bits ← YggRep.BitsFromBits[entry.vDoc.contents.bits];
scratchVDocUnderMonitor.tid ← transID;
RedBlackTree.Insert[self: didCache, insertKey: scratchVDocUnderMonitor, dataToInsert: NEW[cacheEntryRep ← [0, Now, vDoc]]];
IF mode # read THEN YggTransaction.NotePossibleDocumentUpdate[transID, vDoc];
RETURN[vDoc];
};
IF YggTransaction.IsNullTrans[tid] THEN EXIT;
[transFound, tid] ← YggTransaction.GetParent[tid];
IF ~transFound THEN ERROR;
ENDLOOP;
ReserveDIDInCache:
PUBLIC
ENTRY
PROC [did:
DID, transID: YggEnvironment.TransID] ~ {
Given a DID and a transaction, reserve this DID as being volatized. Calling this procedure obligates the caller to call CacheDID to clear the reservation.
ENABLE UNWIND => {};
val: REF;
scratchVDocUnderMonitor.did ← did;
scratchVDocUnderMonitor.tid ← transID;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
entry ← NARROW[val];
WHILE entry.users # 0 DO WAIT myCondition; ENDLOOP;
entry.users ← 1;
}
ELSE {
RedBlackTree.Insert[self: didCache, insertKey: scratchVDocUnderMonitor, dataToInsert: NEW[cacheEntryRep ← [1, Now, NEW[YggRep.VDocRep ← [did: did, tid: transID]]]]];
};
};
UnreserveDIDInCache:
PUBLIC
ENTRY PROC [did:
DID, transID: YggEnvironment.TransID] ~ {
Undo a reservation.
ENABLE UNWIND => {};
val: REF;
scratchVDocUnderMonitor.did ← did;
scratchVDocUnderMonitor.tid ← transID;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
entry ← NARROW[val];
entry.users ← entry.users - 1;
entry.timeOfLastVolatize ← Now;
BROADCAST myCondition;
}
ELSE ERROR;
};
CacheDID:
PUBLIC
ENTRY PROC [did:
DID, transID: YggEnvironment.TransID, vDoc: YggRep.VDoc] ~ {
Add this document to the cache for the did.
ENABLE UNWIND => {};
val: REF;
scratchVDocUnderMonitor.did ← did;
scratchVDocUnderMonitor.tid ← transID;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
entry ← NARROW[val];
entry.vDoc ← vDoc;
entry.users ← 0;
entry.timeOfLastVolatize ← Now;
BROADCAST myCondition;
}
ELSE {
RedBlackTree.Insert[self: didCache, insertKey: vDoc, dataToInsert: NEW[cacheEntryRep ← [0, Now, vDoc]]];
};
};
InvalidateDID:
PUBLIC
ENTRY PROC [did:
DID, transID: YggEnvironment.TransID] ~ {
Remove this did from the cache.
ENABLE UNWIND => {};
val: REF;
scratchVDocUnderMonitor.did ← did;
scratchVDocUnderMonitor.tid ← transID;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
deletedNode: RedBlackTree.Node ← NIL;
entry ← NARROW[val];
WHILE entry.users # 0 DO WAIT myCondition; ENDLOOP;
scratchVDocUnderMonitor.did ← did; -- WAIT may have changed did/tid
scratchVDocUnderMonitor.tid ← transID;
deletedNode ← RedBlackTree.Delete[self: didCache, deleteKey: scratchVDocUnderMonitor];
deletedNode ← NIL;
};
};
PromoteToParent:
PUBLIC
ENTRY
PROC [did: YggDID.
DID, transID: YggEnvironment.TransID] ~ {
ENABLE UNWIND => {};
val: REF;
parentVal: REF;
transFound: BOOL ← FALSE;
parentTid: YggEnvironment.TransID;
scratchVDocUnderMonitor.did ← did;
scratchVDocUnderMonitor.tid ← transID;
val ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF val #
NIL
THEN {
entry: cacheEntry;
entry ← NARROW[val];
[transFound, parentTid] ← YggTransaction.GetParent[transID];
IF ~transFound THEN ERROR;
scratchVDocUnderMonitor.tid ← parentTid;
parentVal ← RedBlackTree.Lookup[self: didCache, lookupKey: scratchVDocUnderMonitor];
IF parentVal #
NIL
THEN {
parentEntry: cacheEntry;
deletedNode: RedBlackTree.Node ← NIL;
parentEntry ← NARROW[parentVal];
scratchVDocUnderMonitor.tid ← transID;
deletedNode ← RedBlackTree.Delete[self: didCache, deleteKey: scratchVDocUnderMonitor];
deletedNode ← NIL;
parentEntry.vDoc ← entry.vDoc;
parentEntry.vDoc.tid ← parentTid;
IF entry.vDoc.metaAttributesChanged #
NIL
THEN {
IF parentEntry.vDoc.metaAttributesChanged = NIL THEN parentEntry.vDoc.metaAttributesChanged ← entry.vDoc.metaAttributesChanged
ELSE {
last: LIST OF YggRep.metaAttributeMod ← NIL;
FOR lomam:
LIST
OF YggRep.metaAttributeMod ← parentEntry.vDoc.metaAttributesChanged, lomam.rest
UNTIL lomam =
NIL
DO
last ← lomam;
ENDLOOP;
last.rest ← entry.vDoc.metaAttributesChanged;
};
};
}
ELSE {
-- no parent
node: RedBlackTree.Node;
parentEntry: cacheEntry;
scratchVDocUnderMonitor.tid ← transID;
node ← RedBlackTree.Delete[self: didCache, deleteKey: scratchVDocUnderMonitor];
IF node = NIL THEN ERROR;
parentEntry ← NARROW[node.data];
parentEntry.vDoc.tid ← parentTid;
scratchVDocUnderMonitor.tid ← parentTid;
RedBlackTree.InsertNode[self: didCache, nodeToInsert: node, insertKey: scratchVDocUnderMonitor];
};
};
};
SetSizeOfDIDCache:
PUBLIC ENTRY PROC [size:
INT] = {
Remove this did from the cache.
ENABLE UNWIND => {};
desiredSizeOfDIDCache ← size;
};