-- RefText.mesa
-- Operations on mutable garbage-collected strings (REF TEXT).
-- Largely parallel to the Rope interface.
-- MBrown, May 2, 1982 11:04 pm
-- Russ Atkinson, August 26, 1982 5:35 pm

DIRECTORY
Environment USING [Comparison],
Rope USING
[ActionType, Compare, Equal, Find, Map, Match, SkipOver, SkipTo, Text],
Runtime USING
[BoundsFault];

RefText: CEDAR DEFINITIONS IMPORTS Rope, Runtime = BEGIN

-- This interface includes some simple procedures for REF TEXT. As much as possible the
-- operations are parallel to the Rope interface's operations on ROPE.

-- When reading from a REF TEXT, the package treats NIL and "" equivalently
-- (Length[NIL] = 0, Fetch[NIL, 0] raises BoundsFault). But Appending to a NIL
-- REF TEXT raises PointerFault.

-- Only the New operation below allocates collectable storage. If you are doing large
-- numbers of REF TEXT allocations, maybe you should be using ROPE.

-- In a "piece" defined by [s: REF TEXT, start: NAT, len: NAT], len is interpreted as follows:
-- IF start > s.length THEN BoundsFault ELSE len ← MIN[len, s.length-start].
-- The resulting len value is called the "effective len" below.

-- A boolean "case" parameter should be understood to mean "case significant".
-- If case, upper case characters are treated as distinct from lower case characters.
-- If ~case, upper case characters are converted to lower case before comparison.

MaxLen: NAT = LAST[NAT];

-- TEXT allocation procedures

-- Any program can produce a REF to a newly-allocated TEXT by writing
-- t: REF TEXT ← NEW[TEXT[n]];
-- where n is the desired maxLength. This allocates from the default prefixed zone. We provide
-- the New procedure below so that clients of RefText can allocate from a zone dedicated to
-- TEXT.

New: PROC [nChars: NAT] RETURNS [REF TEXT];
-- Allocates a TEXT with length = 0, maxLength = nChars, and returns a REF to it.

-- Some programs allocate and discard TEXT frequently. To improve the performance of these
-- programs, the RefText package manages a small pool of "scratch" TEXTs.
-- The expected usage of this pool is for a client to get a scratch TEXT using the
-- ObtainScratch procedure, manipulate this TEXT for awhile, and then return it to the pool
-- using ReleaseScratch. A client who retains a REF to a scratch TEXT after releasing it is
-- not playing by the rules (the same TEXT will surely be handed out to someone else), but
-- this is still "safe" in the Cedar sense (the storage invariants are not compromised by the error).

ObtainScratch: PROC [nChars: NAT] RETURNS [REF TEXT];
-- ! Error [clientModifiedReleasedText]
-- Returns a REF to a TEXT from with length = 0, maxLength >= nChars. This TEXT is
-- generally obtained from a pool of TEXTs.
-- A call to ObtainScratch is less expensive than New, but ObtainScratch should only be
-- called with the expectation of calling ReleaseScratch (below) later on the resulting TEXT.
-- (It is ok for a client to occasionally "forget" to release a TEXT obtained with this procedure,
-- so for instance there is no need to call ReleaseScratch in UNWIND catch phrases unless
-- UNWIND is expected most of the time!)
-- Raises Error [clientModifiedReleasedText] if the TEXT it wanted to return has
-- been tampered with (in a detectable way) since it was released with ReleaseScratch;
-- this indicates that some client is not playing by the rules.

Error: ERROR [ec: ErrorCode];
ErrorCode: TYPE = { clientModifiedReleasedText };

ReleaseScratch: PROC [t: REF TEXT];
-- Caller asserts that it has no further interest in the TEXT pointed to by t.


-- TEXT manipulation procedures

Append: PROC
[to: REF TEXT, from: REF READONLY TEXT, start: NAT ← 0, len: NAT ← MaxLen];
-- ! PointerFault (if to = NIL)
-- ! BoundsFault (if start > from.length or to.length + effective len > to.maxLength)

AppendChar: PROC [to: REF TEXT, from: CHAR] = INLINE {
-- ! PointerFault (if to = NIL)
-- ! BoundsFault (if to.length = to.maxLength)
TRUSTED {IF to.maxLength = to.length THEN ERROR Runtime.BoundsFault};
to[to.length] ← from;
to.length ← to.length + 1};

Compare: PROC
[s1, s2: REF READONLY TEXT, case: BOOLTRUE]
RETURNS [Environment.Comparison] = INLINE {
-- returns lexicographic comparison of the REF TEXT contents
-- case => case of characters is significant
RETURN [Rope.Compare[TrustTextAsRope[s1], TrustTextAsRope[s2], case]]};

Equal: PROC
[s1, s2: REF READONLY TEXT, case: BOOLTRUE] RETURNS [BOOL] = INLINE {
-- returns s1 = s2 (true iff s1 and s2 contain same sequence of characters,
-- modulo the case parameter) = INLINE {
RETURN [Rope.Equal[TrustTextAsRope[s1], TrustTextAsRope[s2], case]]};

Fetch: PROC
[base: REF READONLY TEXT, index: NAT ← 0] RETURNS [c: CHAR] = INLINE {
-- ! BoundsFault (if base = NIL or index > base.length)
-- fetches indexed character from given REF TEXT.
IF base = NIL OR index > base.length THEN
TRUSTED {ERROR Runtime.BoundsFault};
RETURN [base[index]]};

Find: PROC
[s1, s2: REF READONLY TEXT, pos1: NAT ← 0, case: BOOLTRUE]
RETURNS [INTEGER] = INLINE {
-- returns position in s1 where s2 occurs (starts looking at pos1)
-- does NOT do *-matching (use Match below for this)
-- returns -1 if not found (including pos1 >= Length[s1])
RETURN [Rope.Find[TrustTextAsRope[s1], TrustTextAsRope[s2], pos1, case]]};

Length: PROC [base: REF READONLY TEXT] RETURNS [NAT] = INLINE {
-- returns the length of the REF TEXT (0 if NIL).
RETURN [IF base = NIL THEN 0 ELSE base.length]};

Map: PROC
[s: REF READONLY TEXT, start: NAT ← 0, len: NAT ← MaxLen, action: ActionType]
RETURNS [quit: BOOL] = INLINE {
-- ! BoundsFault (if start > s.length)
-- Applies the action to each char in the given piece of s, in ascending order, until
-- action[char] = TRUE or no more chars.
-- Returns TRUE iff stopped by action[char] = TRUE.
RETURN [Rope.Map[TrustTextAsRope[s], start, len, action]]};
ActionType: TYPE = PROC [CHAR] RETURNS [BOOL];

Match: PROC
[pattern, object: REF READONLY TEXT, case: BOOLTRUE]
RETURNS [BOOL] = INLINE {
-- Returns TRUE iff object matches the pattern, where the pattern may contain
-- * to indicate that 0 or more characters will match.
-- If case is true, then case matters.
RETURN [Rope.Match[TrustTextAsRope[pattern], TrustTextAsRope[object], case]]};

SkipTo: PROC
[s: REF READONLY TEXT, pos: NAT ← 0, skip: REF READONLY TEXT]
RETURNS [NAT] = INLINE {
-- Examine s[pos .. s.length), and return the lowest index in this range such that s[i] is
-- contained in the "skip" string. If no such character exists, return s.length.
RETURN [Rope.SkipTo[TrustTextAsRope[s], pos, TrustTextAsRope[skip]]]};

SkipOver: PROC
[s: REF READONLY TEXT, pos: NAT ← 0, skip: REF READONLY TEXT]
RETURNS [NAT] = INLINE {
-- Examine s[pos .. s.length), and return the lowest index in this range such that s[i] is
-- NOT contained in the skip string. If no such character exists, return s.length.
RETURN [Rope.SkipOver[TrustTextAsRope[s], pos, TrustTextAsRope[skip]]]};

TrustTextAsRope: PROC [text: REF READONLY TEXT] RETURNS [Rope.Text] = INLINE {
TRUSTED {RETURN [LOOPHOLE[text]]}};
-- it is usually OK to treat a REF TEXT as a ROPE
-- you will be surprised only when looking at the type at runtime
-- OR when you alter the text

END.