Trailing-Edge
-
PDP-10 Archives
-
DEC_CMS-20_V1.0_SRC
-
cms/sources/cmptxt.bli
There are no other files named cmptxt.bli in the archive.
MODULE CMPTXT (
IDENT = '1',
%IF
%BLISS(BLISS32)
%THEN
LANGUAGE(BLISS32),
ADDRESSING_MODE(EXTERNAL=LONG_RELATIVE,
NONEXTERNAL=LONG_RELATIVE)
%ELSE
LANGUAGE(BLISS36)
%FI
) =
BEGIN
!
! COPYRIGHT (c) 1982 BY
! DIGITAL EQUIPMENT CORPORATION, MAYNARD, MASS.
!
! THIS SOFTWARE IS FURNISHED UNDER A LICENSE AND MAY BE USED AND COPIED
! ONLY IN ACCORDANCE WITH THE TERMS OF SUCH LICENSE AND WITH THE
! INCLUSION OF THE ABOVE COPYRIGHT NOTICE. THIS SOFTWARE OR ANY OTHER
! COPIES THEREOF MAY NOT BE PROVIDED OR OTHERWISE MADE AVAILABLE TO ANY
! OTHER PERSON. NO TITLE TO AND OWNERSHIP OF THE SOFTWARE IS HEREBY
! TRANSFERRED.
!
! THE INFORMATION IN THIS SOFTWARE IS SUBJECT TO CHANGE WITHOUT NOTICE
! AND SHOULD NOT BE CONSTRUED AS A COMMITMENT BY DIGITAL EQUIPMENT
! CORPORATION.
!
! DIGITAL ASSUMES NO RESPONSIBILITY FOR THE USE OR RELIABILITY OF ITS
! SOFTWARE ON EQUIPMENT WHICH IS NOT SUPPLIED BY DIGITAL.
!
!++
! FACILITY: CMS Library Processor
!
! ABSTRACT:
!
! Compare a master file with a variation file and generate an updated
! master file showing all of the corrections or changes implied by the
! variation.
!
! ENVIRONMENT: VAX/VMS, DS-20
!
! AUTHOR: D. Knight , CREATION DATE: 10-Nov-78
!
!--
!
! TABLE OF CONTENTS
!
FORWARD ROUTINE
BACK_MATCH : NOVALUE, !Backwards search for non-unique matches
CMPINI : NOVALUE, !Set up for use
CMPLINE, !compare two text lines for equality
CMPTXT, !Compare two specified blocks of text
FILL_BUF : NOVALUE, !Fill the text buffers from the file
GET_MST_LINE,
MARK_LINE, !Make sure room exists in buffer for a line
PACK: NOVALUE, !Repack the buffers to eliminate lines no longer needed
TST_UNQ_MAT; !Test for unique match
!
! INCLUDE FILES:
!
%if %bliss(bliss32) %then
LIBRARY 'SYS$LIBRARY:STARLET';
%else
require 'jsys:';
%fi
LIBRARY 'XPORT:'; !XPORT I/O macros
REQUIRE 'SCONFG:'; !CMS configuration options
REQUIRE 'BLISSX:';
REQUIRE 'COMUSR:';
REQUIRE 'HOSUSR:';
!
! MACROS:
!
MACRO
STG(L,M) = OUTSTG(CH$PTR(UPLIT(L)),%CHARCOUNT(L),M) %;
!
! EQUATED SYMBOLS:
!
LITERAL
MAST_BUF=0, !Master buffer flag for MARK_LINE
VAR_BUF=MAST_BUF+1, !Variation buffer flag for MARK_LINE
MAX_CHARS=20000, !Size of working storage buffer
MAX_LINES=800; !Maximum number of lines that can be stored
!
! OWN STORAGE:
!
GLOBAL
$IO_BLOCK(INPUT), !input file IOB
LIB_RD_FLG, !Master file comes from library flag
LIN_MST, !Current line in master buffer
LIN_VAR, !Current line in variation buffer
L_LN_MST, !Last line in master buffer
L_LN_VAR, !Last line in variation buffer
$IO_BLOCK(MASTER), !Master file IOB
MST_EOF, !EOF seen on source file
MST_PTR: REF VECTOR, !Source buffer pointer
MST_SEQ, !master file has explicit sequence information
$IO_BLOCK(OUTPUT), !output file IOB
VAR_EOF, !EOF seen on variation file
VAR_PTR: REF VECTOR, !Variation buffer pointer
in_crc_total;
OWN
IL_PENDING, !variation file line pending
I_ST_CHARS, !Variation buffer max character count in use
I_ST_LINES, !Variation buffer max line count in use
I_TXT_BEG, !Start of variation buffer
I_TXT_END, !End of variation buffer
I_TXT_LOC, !Master pointer to variation buffer
ML_PENDING, !Master file line pending
M_ST_CHARS, !Master buffer max character count in use
M_ST_LINES, !Master buffer max line count in use
M_TXT_BEG, !Start of master buffer
M_TXT_END, !End of master buffer
M_TXT_LOC; !Master pointer to master buffer
!Dispatch pointers to interface routines. These routines are needed
!by the comparison algorithm, but the details of which vary from
!command to command. When CMPINI is called, it is passed the identities
!of these routines. DO NOT attempt to do without them.
OWN
CHK_MST_GEN, !Keep track of insertions or deletions
CHK_MST_OK, !Test line for legality for processing
PRC_DIFF, !Process the differences seen
RD_VAR_LIN; !Read a line from the variation file
!
! EXTERNAL REFERENCES:
!
EXTERNAL
TEST : VECTOR; !Test control vector
EXTERNAL LITERAL
s_bdcksum,
s_miscksum,
s_readerr;
EXTERNAL ROUTINE
aschex,
BADXPO,
BUG, !Error in STEP
CMP_TEXT,
crccalc,
DECASC,
ers,
ersxpo,
GET_STG_CT, !Get size of string
OUTSTG, !Output text string
PUT_STG_CT; !Save size of string
ROUTINE BACK_MATCH (CUR_MST,CUR_VAR,CNTRM,CNTRV) : NOVALUE =
!++
! FUNCTIONAL DESCRIPTION:
!
! Back up over as many matching lines as can be found contiguously.
! It is necessary to be very careful here, since some of the master
! lines are control lines and must be ignored.
!
! FORMAL PARAMETERS:
!
! CUR_MST - current position in master buffer.
! CUR_VAR - current position in variation buffer.
! CNTRM - address of cell for storing master match count
! CNTRV - address of cell for storing variation match count
!
! IMPLICIT INPUTS:
!
! LIN_MST - first line in master buffer
! LIN_VAR - first line in variation buffer
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! NONE.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
LABEL
OUTER;
!Start one line before the current line.
.CNTRM=1;
.CNTRV=1;
OUTER: BEGIN
!Look for duplicate lines preceeding current line
REPEAT
BEGIN
!Quit if backing up too far
IF
.CUR_VAR-..CNTRV LSS .LIN_VAR
THEN
EXITLOOP;
IF
.CUR_MST-..CNTRM LSS .LIN_MST
THEN
EXITLOOP;
!Skip over any non-significant lines in master file
WHILE
NOT (.CHK_MST_OK)(.CUR_MST-..CNTRM)
DO
BEGIN
.CNTRM=..CNTRM+1;
IF
.CUR_MST-..CNTRM LSS .LIN_MST
THEN
LEAVE OUTER
END;
!See if line matches
IF
NOT CMPLINE(.CUR_MST-..CNTRM,.CUR_VAR-..CNTRV)
THEN
EXITLOOP;
!It does, back up one more line
.CNTRM=..CNTRM+1;
.CNTRV=..CNTRV+1
END
END;
!Count of actual lines matched in each buffer
.CNTRM=..CNTRM-1;
.CNTRV=..CNTRV-1
END; !End of BACK_MATCH
GLOBAL ROUTINE CMPINI (LIBRD,C_GEN_ADR,C_OK_ADR,DIFF_ADR,RD_LIN_ADR) : NOVALUE =
!++
! FUNCTIONAL DESCRIPTION:
!
! Set up the various linkages and buffers required for the comparison
! algorithm.
!
! FORMAL PARAMETERS:
!
! LIBRD - if true, master file has column 1 reserved for control functions.
! C_GEN_ADR - address of routine to keep track of insertions or deletions.
! 0 if no routine needed.
! C_OK_ADR - Address of routine to check line for legality
! DIFF_ADR - Address of routine to process differences seen
! RD_LIN_ADR - Address of routine to read a variation line.
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! NONE.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
!Set up linkages
LIB_RD_FLG=.LIBRD;
CHK_MST_GEN=.C_GEN_ADR;
CHK_MST_OK=.C_OK_ADR;
PRC_DIFF=.DIFF_ADR;
RD_VAR_LIN=.RD_LIN_ADR;
!Set up master pointers
LIN_MST=0;
LIN_VAR=0;
L_LN_MST=.LIN_MST;
L_LN_VAR=.LIN_VAR;
MST_EOF=FALSE;
VAR_EOF=FALSE;
!Set up variation buffer
IF
.TEST[0] AND
.TEST[1] NEQ -1
THEN
I_ST_CHARS=.TEST[1]
ELSE
I_ST_CHARS=MAX_CHARS;
$XPO_GET_MEM(CHARACTERS=.I_ST_CHARS,RESULT=I_TXT_LOC);
I_TXT_END=.I_TXT_LOC;
I_TXT_BEG=.I_TXT_END;
!Set up master buffer
IF
.TEST[0] AND
.TEST[2] NEQ -1
THEN
M_ST_CHARS=.TEST[2]
ELSE
M_ST_CHARS=MAX_CHARS;
$XPO_GET_MEM(CHARACTERS=.M_ST_CHARS,RESULT=M_TXT_LOC);
M_TXT_END=.M_TXT_LOC;
M_TXT_BEG=.M_TXT_END;
!Allocate memory for master line pointers
IF
.TEST[0] AND
.TEST[4] NEQ -1
THEN
M_ST_LINES=.TEST[4]
ELSE
M_ST_LINES=MAX_LINES;
$XPO_GET_MEM(FULLWORDS=.M_ST_LINES,RESULT=MST_PTR);
IF
.TEST[0] AND
.TEST[3] NEQ -1
THEN
I_ST_LINES=.TEST[3]
ELSE
I_ST_LINES=MAX_LINES;
$XPO_GET_MEM(FULLWORDS=.I_ST_LINES,RESULT=VAR_PTR);
IL_PENDING=FALSE;
ML_PENDING=FALSE;
FILL_BUF()
END; !End of CMPINI
ROUTINE CMPLINE (S_LINE,V_LINE) =
!++
! FUNCTIONAL DESCRIPTION:
!
! Compare the specified lines in source and variation buffers
!
! FORMAL PARAMETERS:
!
! S_LINE - line number of source line
! V_LINE - line number of variation line
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! TRUE - match
! FALSE - no match
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
LOCAL
MST_LGT,
MST_STG,
VAR_LGT,
VAR_STG;
!End of file on both is a match
IF
.S_LINE GEQ .L_LN_MST AND
.V_LINE GEQ .L_LN_VAR
THEN
RETURN TRUE;
!Make sure range is reasonable
IF
.S_LINE GEQ .L_LN_MST OR
.V_LINE GEQ .L_LN_VAR
THEN
RETURN FALSE;
!Point to master string
MST_STG=.MST_PTR[.S_LINE-.LIN_MST];
MST_LGT=GET_STG_CT(MST_STG);
!Point to variation string
VAR_STG=.VAR_PTR[.V_LINE-.LIN_VAR];
VAR_LGT=GET_STG_CT(VAR_STG);
!Now compare the two specified strings
IF
NOT .MST_SEQ AND
NOT .MASTER_IOB[IOB$V_SEQUENCED] AND
NOT .INPUT_IOB[IOB$V_SEQUENCED]
THEN
!No sequence information to worry about
BEGIN
IF
.LIB_RD_FLG
THEN
CH$EQL(.MST_LGT-1,CH$PLUS(.MST_STG,1),.VAR_LGT,.VAR_STG)
ELSE
CH$EQL(.MST_LGT,.MST_STG,.VAR_LGT,.VAR_STG)
END
ELSE
!Extra work is required in the comparison
CMP_TEXT(.MST_LGT,.MST_STG,.VAR_LGT,.VAR_STG)
END; !End of CMPLINE
GLOBAL ROUTINE CMPTXT (EN_MST,EN_VAR) =
!++
! FUNCTIONAL DESCRIPTION:
!
! Compare two files, one being the "master", the other
! being the "variation". Generate a file from the
! differences.
!
! The algorithm is relatively simple. First, look for two lines that
! match in the two files. Once they are found, make sure that they
! comprise a unique match, namely, there are no other lines which
! could also match similarly (if they are not unique, assume that no
! match exists). Once a unique match is found, scan the text backwards
! and find as many matching lines as possible (this gets rid of redundant
! non-unique matches). This establishes the boundaries of matched lines
! which then can be passed to OUTDIFF to place in the output file.
!
! The purpose of this procedure is to prevent false matches which may
! occur because of multiple blank lines or multiple lines of "boilerplate"
! which so often occur and cause unwarranted matches.
!
! IMPORTANT NOTE: This routine is occasionally called
! recursively to resolve potential mis-match situations.
!
! FORMAL PARAMETERS:
!
! EN_MST - address of last master line to be scanned in this call
! EN_VAR - address of last variation line to be scanned in this call
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! Standard GETELM returns as described in SCONFG.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
LABEL
OUTER;
LOCAL
F_M_NON, !First non-unique master line matched
F_V_NON, !First non-unique variation line matched
LAST_L_MATCH, !Marks previous line as having matched
last_prev_buf, !Last line of previous buffer was significant
MST_DMP, !Buffer dump toggle
M_PTR, !Master line pointer
TOGGLE, !Direction of comparison toggle switch
V_PTR; !Variation line pointer
!Set the start of the comparison from master to variation for a default
TOGGLE=TRUE;
!Set up for alternate dumping of buffers when search failure occurs
MST_DMP=FALSE;
!Fake a last line being significant
last_prev_buf=true;
!No previous match has occurred
!This is used to perform a fast advance over text when both buffers
!are in sync and the text is currently matching
LAST_L_MATCH=TRUE;
!We always start at the beginning of the buffer
M_PTR=.LIN_MST;
V_PTR=.LIN_VAR;
!Set no non-unique matches seen
F_M_NON=-1;
!Perform the source comparison, generating the output file
!information as matches occur.
REPEAT
OUTER: BEGIN
!Make sure buffers are full, if possible
FILL_BUF();
!Now see if any of the material at the beginning of the buffer is
! a continuation of insignificant data at the end of the previous
! buffer. If so, it can be summarily dumped.
if
not .last_prev_buf
then
begin
incr m_cntr from .lin_mst to .l_ln_mst do
begin
if
(.chk_mst_ok)(.m_cntr)
then
!good line seen, terminate scan
begin
!reset flag
last_prev_buf=true;
!don't try anything if nothing was seen
if
.m_cntr neq .lin_mst
then
begin
!output what we don't need
(.prc_diff)(.m_cntr-1,-1);
!now reset the world to the beginning
last_l_match=true;
f_m_non=-1;
m_ptr=.lin_mst;
v_ptr=.lin_var
end;
leave outer
end
end;
!output entire null buffer
(.prc_diff)(.l_ln_mst,-1);
!See if we just output the last one
if
.mst_eof
then
!dump the rest of the variation text also
! and go away quietly
begin
do
begin
fill_buf();
(.prc_diff)(-1,.l_ln_var)
end
until
.var_eof;
exitloop
end;
!now reset the world to the beginning
last_l_match=true;
f_m_non=-1;
m_ptr=.lin_mst;
v_ptr=.lin_var;
leave outer
end;
!See which direction the comparison is to proceed.
IF
.TOGGLE
THEN
!Compare current master line to range of variation lines
BEGIN
!(Master file has control lines also, ignore these)
IF
(.CHK_MST_OK)(.M_PTR)
THEN
!The line is a good line for the comparison
BEGIN
!Scan range of lines looking for a unique match in the text
INCR V_CNTR FROM .LIN_VAR TO .V_PTR DO
BEGIN
IF
TST_UNQ_MAT(LAST_L_MATCH,F_M_NON,F_V_NON,.EN_MST,.EN_VAR,.M_PTR,.V_CNTR)
THEN
BEGIN
!Reset working pointers to new buffer head line and try again
M_PTR=.LIN_MST;
V_PTR=.LIN_VAR;
!Make sure we do not exceed the range allowed in
!a recursive call. Quit if this range is exhausted
IF
.EN_MST NEQ L_LN_MST AND
(.M_PTR GEQ ..EN_MST OR
.V_PTR GEQ ..EN_VAR)
THEN
RETURN G_OK;
LEAVE OUTER
END
END;
!If the end of one buffer is reached before the other
!the comparison reverts to the simple anything goes type of
!of match.
IF
.V_PTR LSS ..EN_VAR
THEN
BEGIN
V_PTR=.V_PTR+1;
TOGGLE=FALSE
END
ELSE
BEGIN
IF
.M_PTR LSS ..EN_MST
THEN
M_PTR=.M_PTR+1
END
END
ELSE
!The line seen was a control or deleted line from the master.
!Skip over it without using it, but make sure to notice
!when we run out of lines.
BEGIN
IF
.M_PTR LSS ..EN_MST
THEN
M_PTR=.M_PTR+1
ELSE
BEGIN
IF
.V_PTR LSS ..EN_VAR
THEN
BEGIN
V_PTR=.V_PTR+1;
TOGGLE=FALSE
END
END
END
END
ELSE
!Compare current variation line to range of master lines
BEGIN
INCR M_CNTR FROM .LIN_MST TO .M_PTR DO
BEGIN
!A comparison to a master control or comment line is
!a guaranteed failure.
IF
(.CHK_MST_OK)(.M_CNTR)
THEN
!The line is significant, look for a unique match
BEGIN
IF
TST_UNQ_MAT(LAST_L_MATCH,F_M_NON,F_V_NON,.EN_MST,.EN_VAR,.M_CNTR,.V_PTR)
THEN
BEGIN
!Reset working pointers to new buffer head line and try again
M_PTR=.LIN_MST;
V_PTR=.LIN_VAR;
!Make sure we do not exceed the range allowed in
!a recursive call. Quit if this range is exhausted
IF
.EN_MST NEQ L_LN_MST AND
(.M_PTR GEQ ..EN_MST OR
.V_PTR GEQ ..EN_VAR)
THEN
RETURN G_OK;
LEAVE OUTER
END
END
END;
!See if we reached the end of the master buffer first.
IF
.M_PTR LSS ..EN_MST
THEN
BEGIN
M_PTR=.M_PTR+1;
TOGGLE=TRUE
END
ELSE
BEGIN
IF
.V_PTR LSS ..EN_VAR
THEN
V_PTR=.V_PTR+1
END
END;
!See if this is the end of a recursive scan
IF
.EN_MST NEQ L_LN_MST AND
(.M_PTR GEQ ..EN_MST OR
.V_PTR GEQ ..EN_VAR)
THEN
EXITLOOP;
!Watch for no more text in either buffer
IF
.M_PTR GEQ .L_LN_MST AND
.V_PTR GEQ .L_LN_VAR
THEN
BEGIN
IF
.M_PTR GTR .L_LN_MST OR
.V_PTR GTR .L_LN_VAR
THEN
BUG(LIT('Pointer out of range in CMPTXT'));
IF
.MST_EOF AND
.VAR_EOF
THEN
BEGIN
!Dump everything left
(.PRC_DIFF)(.L_LN_MST,.L_LN_VAR);
EXITLOOP
END;
!See if master buffer end line is significant (i.e. -
! it was successfully compared to the variation line).
! If it isn't, you must give precedence to dumping the
! master buffer, otherwise some data from the variation
! buffer may be inserted in the output file in the
! wrong place.
if
.lin_mst lss .l_ln_mst
then
if
not (.chk_mst_ok)(.l_ln_mst-1)
then
last_prev_buf=false;
!Process various end of buffer conditions
IF
.MST_EOF
THEN
begin
!If the last line in the master buffer is not significant,
! it is unsafe to dump the variation file, so just dump
! everything and go away.
if
not .last_prev_buf
then
begin
!dump what we have now
(.prc_diff)(.l_ln_mst,.l_ln_var);
!loop through the remainder of the variation until EOF
! is reached.
do
begin
fill_buf();
(.prc_diff)(-1,.l_ln_var)
end
until
.var_eof;
exitloop
end;
!Dump variation buffer if there is no more text
!in the master file
(.PRC_DIFF)(-1,.L_LN_VAR)
end
ELSE
IF
.VAR_EOF
THEN
!Dump the master buffer if there is no more text
!in the variation file
(.PRC_DIFF)(.L_LN_MST,-1)
ELSE
!Neither file has run out, dump the buffer
!which was not dumped last time
! (unless the last line was not significant, then
! always dump the master).
BEGIN
IF
.MST_DMP or
not .last_prev_buf
THEN
begin
mst_dmp=false;
(.PRC_DIFF)(.L_LN_MST,-1)
end
ELSE
begin
mst_dmp=true;
(.PRC_DIFF)(-1,.L_LN_VAR)
end
END;
!Reset the world to the beginning
LAST_L_MATCH=TRUE;
F_M_NON=-1;
M_PTR=.LIN_MST;
V_PTR=.LIN_VAR
END
END;
G_OK
END; !End of CMPTXT
ROUTINE FILL_BUF : NOVALUE =
!++
! FUNCTIONAL DESCRIPTION:
!
! Place as many lines as possible into the two buffers.
!
! The lines are placed in the buffer as a count followed by "count"
! number of characters. The lines are pointed to through
! the MST_PTR and VAR_PTR vectors. To access line "n", find the
! character pointer in xxx_PTR[.n] as required.
!
! FORMAL PARAMETERS:
!
! NONE.
!
! IMPLICIT INPUTS:
!
! LIN_MST, LIN_VAR, L_LN_MST, L_LN_VAR are used for buffer control
!
! IMPLICIT OUTPUTS:
!
! MST_EOF and VAR_EOF are set respectively for end of file.
! ML_PENDING and IL_PENDING are set as required where a line
! has been read but cannot be placed in the buffer.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! NONE.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
LOCAL
PTR,
SEQ_BUF : VECTOR[CH$ALLOCATION(MAX_NUM_SIZE+5)],
SEQ_LEN;
OWN
M_LGT,
M_PTR,
V_LGT,
V_PTR;
!Fill master buffer, note that the master file can
!have IOB$V_SEQUENCED set only if this is CMS DIFF
WHILE
NOT .MST_EOF
DO
!No end of file seen
BEGIN
!Get a line
IF
NOT .ML_PENDING
THEN
!No line already exists in the input buffer, so read a new one.
BEGIN
LOCAL
COMPLETION;
COMPLETION=GET_MST_LINE(M_LGT,M_PTR);
!Terminate early if end-of-file is seen
IF
.COMPLETION EQL STEP$_EOF
THEN
BEGIN
MST_EOF=TRUE;
EXITLOOP
END;
!Something is basically wrong!
IF
NOT .COMPLETION
THEN
!ERROR
ersxpo(s_readerr,.completion,
cat('Error reading file '
,master_iob[iob$t_resultant]))
END;
!Pack the text line if necessary
IF
NOT .LIB_RD_FLG AND
.MASTER_IOB[IOB$V_SEQUENCED]
THEN
BEGIN
SEQ_LEN=DECASC(.MASTER_IOB[IOB$G_SEQ_NUMB],CH$PTR(SEQ_BUF));
!Find space for the line
PTR=MARK_LINE(MAST_BUF,.M_LGT+.SEQ_LEN+1)
END
ELSE
!Find space for the line
PTR=MARK_LINE(MAST_BUF,.M_LGT);
IF
.PTR EQL 0 OR
.L_LN_MST-.LIN_MST GEQ .M_ST_LINES
THEN
!No room for the line or its pointer, mark it pending
BEGIN
ML_PENDING=TRUE;
EXITLOOP
END;
!Mark good lines in master file
IF
.CHK_MST_GEN NEQ 0
THEN
(.CHK_MST_GEN)(.M_PTR,.M_LGT);
!place pointer to line in control vector
MST_PTR[.L_LN_MST-.LIN_MST]=.PTR;
L_LN_MST=.L_LN_MST+1;
!Mark the line as having been processed
ML_PENDING=FALSE;
!Place the actual line in the buffer
IF
NOT .MASTER_IOB[IOB$V_SEQUENCED]
THEN
!No sequencing
BEGIN
PUT_STG_CT(.M_LGT,PTR);
M_TXT_END=CH$MOVE(.M_LGT,.M_PTR,.PTR)
END
ELSE
BEGIN
PUT_STG_CT(.M_LGT+.SEQ_LEN+1,PTR);
PTR=CH$MOVE(.SEQ_LEN,CH$PTR(SEQ_BUF),.PTR);
CH$WCHAR_A(%C';',PTR);
M_TXT_END=CH$MOVE(.M_LGT,.M_PTR,.PTR)
END
END;
!Fill input buffer
WHILE
NOT .VAR_EOF
DO
!No end of file seen, proceed
BEGIN
!Get a line
IF
NOT .IL_PENDING
THEN
!No line already exists in the input buffer, get a new one
BEGIN
LOCAL
COMPLETION;
COMPLETION=(.RD_VAR_LIN)(V_LGT,V_PTR);
!Terminate early if end of file
IF
.COMPLETION EQL STEP$_EOF or .COMPLETION EQL xpo$_end_file
THEN
BEGIN
VAR_EOF=TRUE;
EXITLOOP
END;
!Something important is wrong.
IF
NOT .COMPLETION
THEN
!ERROR
ersxpo(s_readerr,.completion,
cat('Error reading file '
,master_iob[iob$t_resultant]))
END;
!Get sequence number if sequenced
IF
.INPUT_IOB[IOB$V_SEQUENCED]
THEN
BEGIN
!Pick up sequence number
SEQ_LEN=DECASC(.INPUT_IOB[IOB$G_SEQ_NUMB],CH$PTR(SEQ_BUF));
PTR=MARK_LINE(VAR_BUF,.V_LGT+.SEQ_LEN+1)
END
ELSE
!Find space for the line
PTR=MARK_LINE(VAR_BUF,.V_LGT);
IF
.PTR EQL 0 OR
.L_LN_VAR-.LIN_VAR GEQ .I_ST_LINES
THEN
!No room for the line (or maybe its pointer), mark it pending
BEGIN
IL_PENDING=TRUE;
EXITLOOP
END;
!Remember the address where the line will go
VAR_PTR[.L_LN_VAR-.LIN_VAR]=.PTR;
L_LN_VAR=.L_LN_VAR+1;
!Mark the line as being processed
IL_PENDING=FALSE;
!Now place the line in the buffer
IF
NOT .INPUT_IOB[IOB$V_SEQUENCED]
THEN
BEGIN
PUT_STG_CT(.V_LGT,PTR);
I_TXT_END=CH$MOVE(.V_LGT,.V_PTR,.PTR)
END
ELSE
!Sequencing is to be processed
BEGIN
PUT_STG_CT(.V_LGT+.SEQ_LEN+1,PTR);
PTR=CH$MOVE(.SEQ_LEN,CH$PTR(SEQ_BUF),.PTR);
CH$WCHAR_A(%C';',PTR);
I_TXT_END=CH$MOVE(.V_LGT,.V_PTR,.PTR)
END
END
END; !End of FILL_BUF
GLOBAL ROUTINE GET_MST_LINE (LGT,PTR) =
!++
! FUNCTIONAL DESCRIPTION:
!
! Get a master line and calcutate the CRC if this is a replace.
!
! FORMAL PARAMETERS:
!
! NONE.
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! NONE.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
OWN
master_line : vector[ch$allocation(3000)]; !line buffer to prevent
!writting into ver mem
LOCAL
COMPLETION;
COMPLETION=$step_get(IOB=MASTER_IOB,FAILURE=0);
IF .completion
THEN
BEGIN
!copy into buffer so that we can change a line. VIRTUAL memory where the
!text resides is wwrite protected.
ch$move(.master_iob[iob$h_string],.master_iob[iob$a_string],
ch$ptr(master_line));
!Point to text
.PTR=ch$ptr(master_line);
.LGT=.MASTER_IOB[IOB$H_STRING];
END;
!+
! Check CRC and take the appropiate action on replace
!-
IF .lib_rd_flg
THEN
BEGIN
! end of file means no crc record exists
IF .completion EQL step$_eof
THEN
BEGIN
BIND
file_spec = .master_iob[iob$a_file_spec] : $str_descriptor();
LOCAL
element_buf : VECTOR[CH$ALLOCATION(extended_file_spec)],
element_len;
! copy file name and skip over cms$lib:
element_len = .file_spec[str$h_length] - %CHARCOUNT(lib);
ch$move(.element_len,
ch$plus(.file_spec[str$a_pointer],%CHARCOUNT(lib)),
ch$ptr(element_buf));
ERS(s_miscksum,cat('Missing checksum in ',
(.element_len,ch$ptr(element_buf)),
'; Use VERIFY/REPAIR'));
END;
! if we found a crc line verify that it is correct
IF .completion AND ch$eql(4,ch$ptr(UPLIT('*/C:')),4,..ptr)
THEN
BEGIN
LOCAL
crc_len,
crc_ptr,
crc;
crc_len = ..lgt - 4;
crc_ptr = ch$plus(..ptr,4);
crc = aschex(crc_ptr,crc_len);
IF .crc NEQ .in_crc_total
THEN
BEGIN
BIND
file_spec=.master_iob[iob$a_file_spec] : $str_descriptor();
LOCAL
element_buf : VECTOR[CH$ALLOCATION(extended_file_spec)],
element_len;
! copy file name and skip over cms$lib:
element_len = .file_spec[str$h_length] - %CHARCOUNT(lib);
ch$move(.element_len,
ch$plus(.file_spec[str$a_pointer],%charcount(lib)),
ch$ptr(element_buf));
ERS(s_bdcksum,cat('Bad checksum in ',
(.element_len,ch$ptr(element_buf)),
'; Use VERIFY/REPAIR'));
END
ELSE
RETURN step$_eof;
END;
! otherwise calculate the crc and total it
IF .completion
THEN
BEGIN
LOCAL
crc_count;
crc_count = crccalc(..lgt,..ptr);
in_crc_total = .crc_count + .in_crc_total;
END;
END;
.COMPLETION
END; !End of GET_MST_LINE
ROUTINE MARK_LINE (BUFFER,SIZE) =
!++
! FUNCTIONAL DESCRIPTION:
!
! Find room in text buffer for line
!
! FORMAL PARAMETERS:
!
! BUFFER - Address of buffer to be used, either M_TXT_BUF or
! I_TXT_BUF.
! SIZE - size of line to be entered.
!
! IMPLICIT INPUTS:
!
! Buffer control parameters x_TXT_BEG, x_TXT_BUF, x_TXT_END.
!
! IMPLICIT OUTPUTS:
!
! Buffer control parameters are updated.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! 0 - no room
! <>0 - character pointer to space found
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
LOCAL
BUF_PTR,
CHARS,
TEXT_BEG,
TEXT_BUF,
TEXT_END;
IF
.BUFFER EQL VAR_BUF
THEN
BEGIN
CHARS=.I_ST_CHARS;
TEXT_BEG=I_TXT_BEG;
TEXT_BUF=.I_TXT_LOC;
TEXT_END=I_TXT_END
END
ELSE
BEGIN
CHARS=.M_ST_CHARS;
TEXT_BEG=M_TXT_BEG;
TEXT_BUF=.M_TXT_LOC;
TEXT_END=M_TXT_END
END;
!Check boundary conditions to make sure no catastrophe can happen
IF
CH$DIFF(..TEXT_BEG,.TEXT_BUF) LSS 0 OR
CH$DIFF(..TEXT_BEG,CH$PLUS(.TEXT_BUF,.CHARS)) GTR 0 OR
CH$DIFF(..TEXT_END,.TEXT_BUF) LSS 0 OR
CH$DIFF(..TEXT_END,CH$PLUS(.TEXT_BUF,.CHARS)) GTR 0
THEN
BUG(LIT('Buffer pointer out of range (MARK_LINE)'));
!See if there is enough room for the line
!first try simple case.
IF
CH$DIFF(..TEXT_END,..TEXT_BEG) GEQ 0
THEN
!TEXT_END follows TEXT_BEG
BEGIN
!Is the buffer empty?
IF
CH$DIFF(..TEXT_END,..TEXT_BEG) EQL 0
THEN
!Yes
BEGIN
!Make sure a line will fit the empty buffer
IF
.SIZE+2 GEQ .CHARS
THEN
BUG(LIT('Illegal buffer size definition (MARK_LINE)'));
.TEXT_BEG=.TEXT_BUF;
.TEXT_END=..TEXT_BEG;
RETURN ..TEXT_END
END
ELSE
!buffer is not empty
BEGIN
!Make sure there is room at the end
IF
CH$DIFF(CH$PLUS(.TEXT_BUF,.CHARS),..TEXT_END) GTR .SIZE+2
THEN
RETURN ..TEXT_END
ELSE
!Try for room at the beginning
IF
CH$DIFF(..TEXT_BEG,.TEXT_BUF) GTR .SIZE+2
THEN
RETURN .TEXT_BUF
ELSE
!No room
RETURN 0
END
END
ELSE
!TEXT_END precedes TEXT_BEG (hole in middle)
BEGIN
!Make sure there is room
IF
CH$DIFF(..TEXT_BEG,..TEXT_END) GTR .SIZE+2
THEN
RETURN ..TEXT_END
END;
!No room
0
END; !End of MARK_LINE
GLOBAL ROUTINE PACK (M_LINE,V_LINE) : NOVALUE =
!++
! FUNCTIONAL DESCRIPTION:
!
! Repack the two text buffers to remove lines which are no longer needed.
! Repacking is done by shuffling down the MST_PTR and VAR_PTR tables
! to reflect the changes made in the buffer. There is no need to do
! anything or move any physical text in the buffers proper.
!
! FORMAL PARAMETERS:
!
! M_LINE - line number of last line to be discarded in master (-1 if not to be packed)
! V_LINE - line number of last line to be discarded in variation (-1 if not to be packed)
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! NONE.
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
!The lines have been correctly output
!So the buffer is now to be repacked
IF
.M_LINE NEQ -1
THEN
BEGIN
!Repack source lines
INCR I FROM 0 TO .L_LN_MST-.M_LINE-2 DO
MST_PTR[.I]=.MST_PTR[.M_LINE-.LIN_MST+.I+1];
!Reset master line pointers and flush lines thrown away
IF
.M_LINE LSS .L_LN_MST-1
THEN
BEGIN
LIN_MST=.M_LINE+1;
M_TXT_BEG=.MST_PTR[0]
END
ELSE
BEGIN
LIN_MST=.L_LN_MST;
M_TXT_END=.M_TXT_LOC;
M_TXT_BEG=.M_TXT_LOC
END
END;
IF
.V_LINE NEQ -1
THEN
BEGIN
!Repack variation lines
INCR I FROM 0 TO .L_LN_VAR-.V_LINE-2 DO
VAR_PTR[.I]=.VAR_PTR[.V_LINE-.LIN_VAR+.I+1];
!Reset variation line pointer and flush the lines thrown away
IF
.V_LINE LSS .L_LN_VAR-1
THEN
BEGIN
LIN_VAR=.V_LINE+1;
I_TXT_BEG=.VAR_PTR[0]
END
ELSE
BEGIN
LIN_VAR=.L_LN_VAR;
I_TXT_END=.I_TXT_LOC;
I_TXT_BEG=.I_TXT_LOC
END
END
END; !End of PACK
ROUTINE TST_UNQ_MAT (LAST_MAT,M_NONUN,V_NONUN,EN_MST,EN_VAR,M_PNT,V_PNT) =
!++
! FUNCTIONAL DESCRIPTION:
!
! Look for a match at the current line. If found, make sure it is
! unique or the previous line is part of a good match.
! Also make sure that a smaller sub-match is not possible. If it
! is, recall the comparison algorithm with a restricted range.
!
! FORMAL PARAMETERS:
!
! LAST_MAT - address of the cell containing the last match flag
! M_NONUN - address of the master non-unique match flag
! V_NONUN - address of the variation non-unique match flag
! EN_MST - address of the location containing the last buffer line to be scanned
! EN_VAR - address of the variation last buffer line to be scanned
! M_PNT - current working line pointer in the master buffer
! V_PNT - current working line pointer in the variation buffer
!
! IMPLICIT INPUTS:
!
! NONE.
!
! IMPLICIT OUTPUTS:
!
! NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
! TRUE - special exit to restart loop.
! FALSE - normal exit
!
! SIDE EFFECTS:
!
! NONE.
!
!--
BEGIN
!Try for a match
IF
CMPLINE(.M_PNT,.V_PNT)
THEN
!Match found
BEGIN
!See if the comparison is unique or the previous comparison was unique
IF
..LAST_MAT OR
BEGIN
!Look at all lines following the matched
!lines to make sure there are no other matches
INCR V1_CNTR FROM .V_PNT+1 TO ..EN_VAR DO
BEGIN
IF
CMPLINE(.M_PNT,.V1_CNTR)
THEN
EXITLOOP 0
END
END
NEQ 0 AND
BEGIN
!This comparison must be done in both directions
!for completeness
INCR M1_CNTR FROM .M_PNT+1 TO ..EN_MST DO
BEGIN
IF
(.CHK_MST_OK)(.M1_CNTR)
THEN
BEGIN
IF
CMPLINE(.M1_CNTR,.V_PNT)
THEN
EXITLOOP 0
END
END
END
NEQ 0
THEN
!We now know that the match was unique
BEGIN
!Now back up to the beginning of the overall match if required
IF
NOT ..LAST_MAT
THEN
BEGIN
LOCAL
CNTRM,
CNTRV,
M_TPTR,
V_TPTR;
BACK_MATCH(.M_PNT,.V_PNT,CNTRM,CNTRV);
!See if we should scan the smaller range over
IF
.M_PNT-.LIN_MST GTR 0 AND
.V_PNT-.LIN_VAR GTR 0 AND
..M_NONUN NEQ -1 AND
..M_NONUN LEQ .M_PNT-.CNTRM AND
..V_NONUN LEQ .V_PNT-.CNTRV
THEN
BEGIN
M_TPTR=.M_PNT-.CNTRM;
V_TPTR=.V_PNT-.CNTRV;
CMPTXT(M_TPTR,V_TPTR);
END;
!Output the duplicate lines
REPEAT
BEGIN
!Ignore non-significant lines in master file
WHILE
NOT (.CHK_MST_OK)(.M_PNT-.CNTRM) AND
.CNTRM NEQ 0
DO
CNTRM=.CNTRM-1;
IF
.CNTRV EQL 0 OR
.CNTRM EQL 0
THEN
EXITLOOP;
(.PRC_DIFF)(.M_PNT-.CNTRM,.V_PNT-.CNTRV);
CNTRM=.CNTRM-1;
CNTRV=.CNTRV-1
END;
!Make sure it really works
IF
.CNTRM NEQ 0 OR
.CNTRV NEQ 0
THEN
BUG(LIT('Error in TST_UNQ_MAT control loop'));
END;
!Once there, we can output the complete match
(.PRC_DIFF)(.M_PNT,.V_PNT);
!Reset working pointers
!and restart the loop
.M_NONUN=-1;
.LAST_MAT=TRUE;
RETURN TRUE
END
ELSE
!Non-unique match, remember where the first one was
BEGIN
IF
..M_NONUN EQL -1
THEN
BEGIN
.M_NONUN=.M_PNT;
.V_NONUN=.V_PNT
END
END
END
ELSE
.LAST_MAT=FALSE;
FALSE
END; !End of TST_UNQ_MAT
END !End of Module CMPTXT
ELUDOM