Google
 

Trailing-Edge - PDP-10 Archives - DEC_CMS-20_V1.0_SRC - cms/sources/cmpmrg.bli
There are no other files named cmpmrg.bli in the archive.
MODULE CMPMRG	(
		IDENT = '1',
		%IF
		    %BLISS(BLISS32)
		%THEN
		    LANGUAGE(BLISS32),
		    ADDRESSING_MODE(EXTERNAL=LONG_RELATIVE,
				    NONEXTERNAL=LONG_RELATIVE)
		%ELSE
		    LANGUAGE(BLISS36)
		%FI
		) =
BEGIN

!
!			COPYRIGHT (c) 1982, 1983 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:
!
!	Merge two generations of an element together
!
! ENVIRONMENT:	VAX/VMS, DS-20
!
! AUTHOR: D. Knight , CREATION DATE: 29-Oct-79
!
!--
!
! TABLE OF CONTENTS
!

FORWARD ROUTINE
	CMPMRG,				!Basic comparison algorithm
	ADV_SEQ : NOVALUE,		!Advance sequence number and check for overflow
	G_COMN_NODE,			!get most recent common ancestor
	G_NUM_LGT,			!get length of decimal string
	GET_CUR_MST,			!check master line for legality
	GET_LIN,			!get variation line
	OUTDIFF: NOVALUE,		!Output the differences found to the output file
	OUTLIN: NOVALUE,		!Output line and audit trail
	SETSEQ : NOVALUE,		!Set sequence field for output
	SETUP,				!Initialize the world
	TERMINATE : NOVALUE,		!Terminate the world
	TEST_CONF,			!test for text conflict
	TEST_GEN;			!check ancestry of a generation

!
! 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
	IOB$H_RESULTANT=$SUB_FIELD(IOB$T_RESULTANT,STR$H_LENGTH) %,
	IOB$A_RESULTANT=$SUB_FIELD(IOB$T_RESULTANT,STR$A_POINTER) %,
	STG(L,M) = OUTSTG(CH$PTR(UPLIT(L)),%CHARCOUNT(L),M) %;

!
! EQUATED SYMBOLS:
!

LITERAL
	GEN_CONF=0,			!Generation conflict
	GEN_MST=GEN_CONF+1,		!Use master generation
	GEN_VAR=GEN_MST+1,		!Use variation generation
	MAX_SEQ=65533;			!TEMPORARY

!
! OWN STORAGE:
!

OWN
	cant_res,			!Can't resolve merge
	COM_GEN,			!Common ancestor generation
	COM_G_LEN,			!Length of common ancestor generation
	COM_G_PTR,			!Pointer to common ancestor generation
	CONFLICT,
	I_OPN,				!Input file open flag
	M_OPN,				!Master file open flag
	MRG_CNT,			!Number of successful merges
	O_OPN,				!Output file open flag
    	OUTFIL_PTR,			!Pointer to output file name
    	OUTFIL_LEN;			!Length of output file


!
! EXTERNAL REFERENCES:
!

external literal
	s_mrgok,			!merge OK message
	s_mrgbad,			!bad merge
	s_mrgerr,			!Can't resolve merge
	s_isthere,			!file already exists
	s_sameline;			!generations on same line of descent

EXTERNAL
    	CHRONO,				!Chronology desired
    	CHRLEN,				!Length of chronology pattern string
    	FETSTS,				!Used to return special status
	INPUT_IOB : $XPO_IOB(),		!Variation file IOB
	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
	LGEN,				!Pointer to generation information for WRT_LINE
	LGEN_L,				!length of generation information for WRT_LINE
	MASTER_IOB : $XPO_IOB(),	!Master file IOB
	MST_EOF,			!EOF seen on master file
	MST_PTR : REF VECTOR,		!Master buffer pointer
	OUTPUT_IOB : $XPO_IOB(),	!Output file IOB
	VAR_EOF,			!EOF seen on variation file
	VAR_PTR : REF VECTOR;		!Variation buffer pointer

EXTERNAL ROUTINE
	ASCDEC,
	badxpo,
	BUG,				!Error in CMS
	BUGXPO,
	CMPINI,				!Set up comparison algorithm
	CMPTXT,				!Compare two texts
	COMAND,
	DATTIM,				!Get current date and time
	DECASC,				!Decimal to ASCII
	ERS,				!User error
	GETACT,				!Get user's name
	GET_LXM,			!Get text lexeme
	GET_STG_CT,			!Get character count
	OUTINI,				!Initialize text output
	OUTNUM,				!Output numeric field
	OUTSTG,				!Output text string
	PACK,				!Repack buffer
	syslp,
	sysmsg,
    	VERNUM,
	WRT_LINE;			!Output line of text, including source audit
GLOBAL ROUTINE CMPMRG (F1_L,F1,F2_L,F2,OFIL_L,OFIL) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Compare two files, one being the "master", the other
!	being the "variation".  Generate a merged source 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.
!
! FORMAL PARAMETERS:
!
!	NONE.
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	Returns the value stored in CONFLICT, which is the total
!	number of conflicts which occurred while trying to merge
!	given file.  If no conflicts, 0 is returned.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	MSG_BUF : VECTOR [CH$ALLOCATION(75)],	! Extended just in case
	MSG_PTR,
	RETVAL,				!Return value temp
	SIZE;

    !Start up the world
    IF
	NOT SETUP(.F1_L,.F1,.F2_L,.F2,.OFIL_L,.OFIL)
    THEN
	BEGIN
	TERMINATE();
	RETURN FALSE
	END;

    OUTFIL_PTR = .OFIL ;
    OUTFIL_LEN = .OFIL_L ;

    !Generate the updated master file
    !This always starts at the beginning
    RETVAL=CMPTXT(L_LN_MST,L_LN_VAR);

    !All is complete, exit quietly
    TERMINATE();

    !Report number of good merges
    MSG_PTR=CH$PTR(MSG_BUF);
    SIZE=DECASC(.MRG_CNT,.MSG_PTR);
    MSG_PTR=CH$PLUS(.MSG_PTR,.SIZE);
    MSG_PTR=CH$MOVE(7,CH$PTR(UPLIT(' change')),.MSG_PTR);
    IF
	.MRG_CNT NEQ 1
    THEN
	CH$WCHAR_A(%C's',MSG_PTR);
    MSG_PTR=CH$MOVE(29,CH$PTR(UPLIT(' successfully merged in file ')),.MSG_PTR);
    msg_ptr=ch$move(.ofil_l, .ofil, .msg_ptr);
    syslp(s_mrgok,CH$DIFF(.MSG_PTR,CH$PTR(MSG_BUF)),CH$PTR(MSG_BUF),0);
    
    !CONFLICT holds a number that is increased by one for each subsequent
    !conflict.  Thus, must check that it is greater than 0, not just not
    !unequal.  

    IF
	.CONFLICT GTR 0
    THEN
	BEGIN

	MSG_PTR=CH$PTR(MSG_BUF);
	MSG_PTR=CH$MOVE(11,CH$PTR(UPLIT('WARNING -- ')),.MSG_PTR);
	SIZE=DECASC(.CONFLICT,.MSG_PTR);
	MSG_PTR=CH$PLUS(.MSG_PTR,.SIZE);
	MSG_PTR=CH$MOVE(15,CH$PTR(UPLIT(' Merge Conflict')),.MSG_PTR);

	IF
	    .CONFLICT GTR 1
	THEN
	    CH$WCHAR_A(%C's',MSG_PTR);
	syslp(s_mrgbad,CH$DIFF(.MSG_PTR,CH$PTR(MSG_BUF)),CH$PTR(MSG_BUF),0)
	END;

!    .RETVAL
     .CONFLICT
    END;				!End of CMPMRG
ROUTINE ADV_SEQ : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Advance sequence number field by one.  Watch for being out of limits
!	and reset if necessary.
!
! FORMAL PARAMETERS:
!
!	NONE.
!
! IMPLICIT INPUTS:
!
!	Sequence number field in output IOB.
!
! IMPLICIT OUTPUTS:
!
!	Sequence number field in output IOB
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    IF
	.OUTPUT_IOB[IOB$G_SEQ_NUMB] GTR MAX_SEQ
    THEN
	OUTPUT_IOB[IOB$G_SEQ_NUMB]=1
    ELSE
	OUTPUT_IOB[IOB$G_SEQ_NUMB]=.OUTPUT_IOB[IOB$G_SEQ_NUMB]+1

    END;				!End of ADV_SEQ
GLOBAL ROUTINE G_COMN_NODE (G1_L,G1,G2_L,G2,F_LGT,F_PTR) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Generate the generation number that is the most recent
!	common ancestor to the two specified
!
! FORMAL PARAMETERS:
!
!	G1 - pointer to generation 1
!	G1_L - length of generation 1
!	G2 - pointer to generation 2
!	G2_L - length of generation 2
!	F_LGT - length of filename to be processed
!	F_PTR - pointer to filename to be processed
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	COM_GEN - buffer where ancestor generation is stored
!	COM_G_LEN - String length of common ancestor
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	TRUE - ancestor generated correctly
!	FALSE - both are on the same line of descent
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	G1_CHR,
	G1_LGT,
	G1_PTR,
	G1_TMP,
	G1_VAL,
	G2_CHR,
	G2_LGT,
	G2_PTR,
	G2_TMP,
	G2_VAL;

    !Setup
    G1_PTR=.G1;
    G1_LGT=.G1_L;
    G2_PTR=.G2;
    G2_LGT=.G2_L;

    COM_G_PTR=CH$PTR(COM_GEN);
    COM_G_LEN=0;

    !Process entire generation expression
    REPEAT
	BEGIN

	LOCAL
	    OLD1_PNT,
	    OLD2_PNT;

	!Get length of integer parts
	G1_TMP=G_NUM_LGT(.G1_PTR,.G1_LGT);
	OLD1_PNT=.G1_PTR;
	G2_TMP=G_NUM_LGT(.G2_PTR,.G2_LGT);
	OLD2_PNT=.G2_PTR;

	!The lengths of both must be non-zero
	IF
	    .G1_TMP EQL 0 OR
	    .G2_TMP EQL 0
	THEN
	    BUG(LIT('Illegal generation expression in G_COMN_NODE'));

	!Values
	G1_VAL=ASCDEC(G1_PTR,.G1_TMP);
	G1_LGT=.G1_LGT-.G1_TMP;
	G2_VAL=ASCDEC(G2_PTR,.G2_TMP);
	G2_LGT=.G2_LGT-.G2_TMP;

	IF
	    .G1_VAL EQL .G2_VAL
	THEN
	    !Integer parts match, more testing is required
	    BEGIN

	    !Place numeric field in COM_GEN
	    COM_G_PTR=CH$MOVE(.G1_TMP,.OLD1_PNT,.COM_G_PTR);
	    COM_G_LEN=.COM_G_LEN+.G1_TMP;

	    !Pick up which branch for G1
	    IF
		.G1_LGT NEQ 0
	    THEN
		BEGIN
		G1_CHR=CH$RCHAR_A(G1_PTR);
		G1_LGT=.G1_LGT-1
		END
	    ELSE
		BEGIN
		ERS(s_sameline,CAT(('Generations '),(.G1_L,.G1),(' and '),
			(.G2_L,.G2),(' of element '),(.F_LGT,.F_PTR),
			('  are on the same line of descent')));
		RETURN FALSE
		END;

	    !Pick up which branch for G2
	    IF
		.G2_LGT NEQ 0
	    THEN
		BEGIN
		G2_CHR=CH$RCHAR_A(G2_PTR);
		G2_LGT=.G2_LGT-1
		END
	    ELSE
		BEGIN
		ERS(s_sameline,CAT(('Generations '),(.G1_L,.G1),(' and '),
			(.G2_L,.G2),(' of element '),(.F_LGT,.F_PTR),
			('  are on the same line of descent')));
		RETURN FALSE
		END;

	    !if the branches are not the same we have the common node
	    IF
		.G1_CHR NEQ .G2_CHR
	    THEN
		RETURN TRUE;

	    !Place the variant letter in the COM_GEN field
	    CH$WCHAR_A(.G1_CHR,COM_G_PTR);
	    COM_G_LEN=.COM_G_LEN+1;

	    !Error if nothing follows branch marker
	    IF
		.G1_LGT EQL 0 AND
		.G2_LGT EQL 0
	    THEN
		!Error, illegal expression
		BUG(LIT('Illegal generation expression in G_COMN_NODE'))

	    END
	ELSE
	    !generations do not match, the lesser of the two is
	    !the common node
	    BEGIN

	    IF
		.G1_VAL GTR .G2_VAL
	    THEN
		!Use G2
		BEGIN

		!Make sure it isn't already the common node
		IF
		    .G2_LGT EQL 0
		THEN
		    BEGIN
	            ERS(s_sameline,CAT(('Generations '),(.G1_L,.G1),(' and '),
			(.G2_L,.G2),(' of element '),(.F_LGT,.F_PTR),
			('  are on the same line of descent')));
		    RETURN FALSE
		    END;

		COM_G_PTR=CH$MOVE(.G2_TMP,.OLD2_PNT,.COM_G_PTR);
		COM_G_LEN=.COM_G_LEN+.G2_TMP
		END
	    ELSE
		!Use G1
		BEGIN

		!Make sure G1 isn't already the common node
		IF
		    .G1_LGT EQL 0
		THEN
		    BEGIN
		    ERS(s_sameline,CAT(('Generations '),(.G1_L,.G1),(' and '),
			(.G2_L,.G2),(' of element '),(.F_LGT,.F_PTR),
			('  are on the same line of descent')));
		    RETURN FALSE
		    END;

		COM_G_PTR=CH$MOVE(.G1_TMP,.OLD1_PNT,.COM_G_PTR);
		COM_G_LEN=.COM_G_LEN+.G1_TMP
		END;

	    RETURN TRUE
	    END

	END;

    !Can't get here from there
    BUG(LIT('Error in G_COMN_NODE'))

    END;				!End of G_COMN_NODE
ROUTINE G_NUM_LGT (PTR,LGT) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Get the length of a decimal string
!
! FORMAL PARAMETERS:
!
!	PTR - pointer to string
!	LGT - length of string
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	Size of integer string
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	C_PTR,
	CNT;

    CNT=0;
    C_PTR=.PTR;

    INCR I FROM 1 TO .LGT DO
	BEGIN

	LOCAL
	    CHAR;

	CHAR=CH$RCHAR_A(C_PTR);

	IF
	    .CHAR GEQ %C'0' AND
	    .CHAR LEQ %C'9'
	THEN
	    CNT=.CNT+1
	ELSE
	    EXITLOOP
	END;

    .CNT

    END;				!End of G_NUM_LGT
ROUTINE GET_CUR_MST (LINE_NUM) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	See if a master line is a legal text line which can be processed
!
! FORMAL PARAMETERS:
!
!	LINE_NUM - line number of line in master buffer
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	TRUE - line is legal line for processing
!	FALSE - line is not to be processed
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    .LINE_NUM LSS .L_LN_MST

    END;				!End of GET_CUR_MST
ROUTINE GET_LIN (LGT,PTR) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Get a variation line from the input file
!
! FORMAL PARAMETERS:
!
!	LGT - address of cell where length is to be placed
!	PTR - address of cell where address of data is placed
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	I/O completion code
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    OWN
	COMPLETION;

    COMPLETION=$step_get(IOB=INPUT_IOB,FAILURE=0);

    .LGT=.INPUT_IOB[IOB$H_STRING];
    .PTR=.INPUT_IOB[IOB$A_STRING];

    .COMPLETION

    END;				!End of GET_LIN
ROUTINE OUTDIFF (M_LINE,V_LINE) : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Output any differences between the master and variation files seen
!	so far.  This recognizes both deletions and insertions.  Comments
!	and control lines are ignored.
!
! FORMAL PARAMETERS:
!
!	M_LINE - Source line pointer
!	V_LINE - Variation line pointer
!
! IMPLICIT INPUTS:
!
!	The lines of text are stored in the master and variation buffers.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	PACK is called to repack the buffer and get rid of the lines that
!	have been output.
!
!--

    BEGIN

    LOCAL
	CONFL,
	COUNT,
	L_PTR,
	L_SIZ;

    IF
	.M_LINE EQL -1 AND
	.V_LINE EQL -1
    THEN
	BUG(LIT('Two null OUTDIFF pointers (CMPMRG)'));

    !Check for potential bug
    IF
	.M_LINE LSS .LIN_MST AND
	.M_LINE NEQ -1
    THEN
	BUG(LIT('Master line pointer out of range in OUTDIFF (CMPMRG)'));

    IF
	.V_LINE LSS .LIN_VAR AND
	.V_LINE NEQ -1
    THEN
	BUG(LIT('Variation line pointer out of range in OUTDIFF (CMPMRG)'));

    CONFL=FALSE;

    !Get number of lines per entry maximum
    IF
	.M_LINE NEQ -1 AND
	.V_LINE NEQ -1
    THEN
	BEGIN
	IF
	    .M_LINE-.LIN_MST GTR .V_LINE-.LIN_VAR
	THEN
	    COUNT=.M_LINE-.LIN_MST
	ELSE
	    COUNT=.V_LINE-.LIN_VAR
	END
    ELSE
    IF
	.M_LINE EQL -1
    THEN
	COUNT=.V_LINE-.LIN_VAR
    ELSE
	COUNT=.M_LINE-.LIN_MST;

    !Make sure there is a change
    IF
	.COUNT NEQ 0
    THEN
	BEGIN
	!Check for conflict in text
	CONFL=TEST_CONF(.M_LINE,.V_LINE);

	IF
	    .CONFL NEQ GEN_CONF
	THEN
	    !No conflict
	    BEGIN

	    !Keep track of successful merges
	    MRG_CNT=.MRG_CNT+1;

	    IF
		.CONFL EQL GEN_MST
	    THEN
		!Output source lines
		BEGIN
		INCR I FROM .LIN_MST TO .M_LINE-1 DO
		    BEGIN
		    L_PTR=.MST_PTR[.I-.LIN_MST];
		    L_SIZ=GET_STG_CT(L_PTR);
		    !Get sequence information
		    IF
			.MASTER_IOB[IOB$V_SEQUENCED]
		    THEN
			!Master is sequenced
			SETSEQ(L_SIZ,L_PTR)
		    ELSE
		    IF
			.INPUT_IOB[IOB$V_SEQUENCED]
		    THEN
			!Variation is sequenced, master is not,
			!the numbers must be faked
			ADV_SEQ();

		    OUTLIN(.L_PTR,.L_SIZ)
		    END
		END
	    ELSE
		!Output variation lines
		BEGIN
		INCR I FROM .LIN_VAR TO .V_LINE-1 DO
		    BEGIN
		    L_PTR=.VAR_PTR[.I-.LIN_VAR];
		    L_SIZ=GET_STG_CT(L_PTR);
		    !Get sequence information
		    IF
			.INPUT_IOB[IOB$V_SEQUENCED]
		    THEN
			!Variation is sequenced
			SETSEQ(L_SIZ,L_PTR)
		    ELSE
		    IF
			.MASTER_IOB[IOB$V_SEQUENCED]
		    THEN
			!Master is sequenced, Variation is not,
			!the numbers must be faked
			ADV_SEQ();

		    OUTLIN(.L_PTR,.L_SIZ)
		    END
		END
	    END
	ELSE
	    !Conflict
	    BEGIN
	    CONFLICT=.CONFLICT+1;

	    !Fake a sequence number if needed
	    IF
		.INPUT_IOB[IOB$V_SEQUENCED] OR
		.MASTER_IOB[IOB$V_SEQUENCED]
	    THEN
		ADV_SEQ();

	    STG('*************** Conflict ',FALSE);
	    OUTNUM(.CONFLICT,FALSE);
	    STG(' ',FALSE);
	    INCR I FROM 1 TO 10 DO STG('*****',FALSE);
	    OUTSTG(0,0,TRUE);

	    !Run through the master text
	    IF
		.M_LINE NEQ -1
	    THEN
		BEGIN
		INCR I FROM .LIN_MST TO .M_LINE-1 DO
		    BEGIN

		    LOCAL
			G_PTR,
			G_LEN;

		    !Read a line
		    L_PTR=.MST_PTR[.I-.LIN_MST];
		    L_SIZ=GET_STG_CT(L_PTR);

		    !Get sequence information
		    IF
			.MASTER_IOB[IOB$V_SEQUENCED]
		    THEN
			!Master is sequenced
			SETSEQ(L_SIZ,L_PTR)
		    ELSE
		    IF
			.INPUT_IOB[IOB$V_SEQUENCED]
		    THEN
			!Fake sequence numbers
			ADV_SEQ();

		    !Pick off the generation value
		    G_PTR=.L_PTR;
		    G_LEN=0;
		    UNTIL CH$RCHAR_A(G_PTR) EQL %C'	' DO G_LEN=.G_LEN+1;

		    IF
			CH$RCHAR(.L_PTR) NEQ %C'*'
		    THEN
			OUTLIN(.L_PTR,.L_SIZ)
		    END
		END;

	    !Process variation text
	    !(fake a sequence number if needed)
	    IF
		.INPUT_IOB[IOB$V_SEQUENCED] OR
		.MASTER_IOB[IOB$V_SEQUENCED]
	    THEN
		ADV_SEQ();

	    INCR I FROM 1 TO 15 DO STG('*****',FALSE);
	    OUTSTG(0,0,TRUE);

	    !Output the text proper
	    IF
		.V_LINE NEQ -1
	    THEN
		BEGIN
		INCR I FROM .LIN_VAR TO .V_LINE-1 DO
		    BEGIN

		    LOCAL
			G_LEN,
			G_PTR;

		    L_PTR=.VAR_PTR[.I-.LIN_VAR];
		    L_SIZ=GET_STG_CT(L_PTR);

		    !Get sequence information
		    IF
			.INPUT_IOB[IOB$V_SEQUENCED]
		    THEN
			!Variation is sequenced
			SETSEQ(L_SIZ,L_PTR)
		    ELSE
		    IF
			.MASTER_IOB[IOB$V_SEQUENCED]
		    THEN
			!Fake the sequence numbers
			ADV_SEQ();

		    !Pick off the generation value
		    G_PTR=.L_PTR;
		    G_LEN=0;
		    UNTIL CH$RCHAR_A(G_PTR) EQL %C'	' DO G_LEN=.G_LEN+1;

		    IF
			CH$RCHAR(.L_PTR) NEQ %C'*'
		    THEN
			OUTLIN(.L_PTR,.L_SIZ)
		    END
		END;

	    !(fake a sequence number, if needed)
	    IF
		.INPUT_IOB[IOB$V_SEQUENCED] OR
		.MASTER_IOB[IOB$V_SEQUENCED]
	    THEN
		ADV_SEQ();

	    STG('******** End of Conflict ',FALSE);
	    OUTNUM(.CONFLICT,FALSE);
	    STG(' ',FALSE);
	    INCR I FROM 1 TO 10 DO STG('*****',FALSE);
	    OUTSTG(0,0,TRUE)
	    END
	END;

    !Now output the unchanged line
    IF
	.M_LINE LSS .L_LN_MST AND
	.M_LINE NEQ -1 AND
	.V_LINE NEQ -1
    THEN
	BEGIN
	L_PTR=.MST_PTR[.M_LINE-.LIN_MST];
	L_SIZ=GET_STG_CT(L_PTR);
	!Get sequence information
	IF
	    .MASTER_IOB[IOB$V_SEQUENCED]
	THEN
	    !Master is sequenced
	    SETSEQ(L_SIZ,L_PTR)
	ELSE
	IF
	    .INPUT_IOB[IOB$V_SEQUENCED]
	THEN
	    !We can use the variation instead, since the text is identical
	    BEGIN
	    L_PTR=.VAR_PTR[.V_LINE-.LIN_VAR];
	    L_SIZ=GET_STG_CT(L_PTR);
	    SETSEQ(L_SIZ,L_PTR)
	    END;

	OUTLIN(.L_PTR,.L_SIZ)
	END;

    !Repack the text
    PACK(.M_LINE,.V_LINE)

    END;				!End of OUTDIFF
ROUTINE OUTLIN (PTR,SIZ) : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Separate the generation number from the source line, place its
!	address and length into the appropriate places and call the central
!	routine for generating the source audits.
!
! FORMAL PARAMETERS:
!
!	PTR - Character pointer to the line containing the embedded generation
!	SIZ - length of the line
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	C_PTR;

    !Ignore deletion lines
    IF
	CH$RCHAR(.PTR) EQL %C'*'
    THEN
	RETURN;

    !Set up to skip over generation information
    C_PTR=.PTR;
    LGEN_L=0;

    !Get the length of the generation and skip over it in the text
    WHILE
	CH$RCHAR_A(C_PTR) NEQ %C'	'
    DO
	LGEN_L=.LGEN_L+1;

    !Set up generation pointer
    LGEN=.PTR;

    !See if this is a page mark being sent to a sequenced file
    IF
	.OUTPUT_IOB[IOB$V_SEQUENCED] AND
	CH$RCHAR(.C_PTR) EQL FORM_FEED AND
	.SIZ-.LGEN_L-1 EQL 1
    THEN
	BEGIN
	OUTSTG(.C_PTR,.SIZ-.LGEN_L-1,TRUE);
	RETURN
	END;

    !Now output the line and its audit
    WRT_LINE(.SIZ-.LGEN_L-1,.C_PTR)

    END;				!End of OUTLIN
ROUTINE SETSEQ (SIZ_ADR,PTR_ADR) : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Pick up the sequence number field and place it and the page number in
!	the IOB.
!
! FORMAL PARAMETERS:
!
!	SIZ_ADR - address of cell containing size of line
!	PTR_ADR - address of pointer to line
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	The sequence number and page number are placed in the output IOB.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	L_TMP,
	SEQ;

    L_TMP=..PTR_ADR;

    SEQ=ASCDEC(.PTR_ADR,0);
    !Skip over ";"
    CH$RCHAR_A(.PTR_ADR);
    !readjust count
    .SIZ_ADR=..SIZ_ADR-CH$DIFF(..PTR_ADR,.L_TMP);
    !Set page and sequence fields
    OUTPUT_IOB[IOB$G_SEQ_NUMB]=.SEQ

    END;			!End of SETSEQ
ROUTINE SETUP (LGT,STR,LGTV,STRV,LGTO,STRO) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Initialize the tables, get the command line, and initially fill
!	the buffers.
!
! FORMAL PARAMETERS:
!
!	LGT - length of master file name to be processed
!	STR - pointer to master file name to be processed
!	LGTV - length of variation file name to be processed
!	STRV - pointer to variation file name to be processed
!
! IMPLICIT INPUTS:
!
!	NONE.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	TRUE - files opened OK
!	FALSE - files not opened successfully
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	FIL: VECTOR[CH$ALLOCATION(EXTENDED_FILE_SPEC)],
	FIL_PTR,
	FIL_SIZ,
	STS;

    M_OPN=FALSE;
    I_OPN=FALSE;
    O_OPN=FALSE;

    STS=$STEP_OPEN(IOB=MASTER_IOB,FILE_SPEC=(.LGT,.STR),FAILURE=0);
    IF
	NOT .STS
    THEN
	BADXPO(.STS,CAT(('Cannot open input file '),(.LGT,.STR)));

    M_OPN=TRUE;

    STS=$STEP_OPEN(IOB=INPUT_IOB,FILE_SPEC=(.LGTV,.STRV),FAILURE=0);
    IF
	NOT .STS
    THEN
	BADXPO(.STS,CAT(('Cannot open input file '),(.LGTV,.STRV)));

    I_OPN=TRUE;

    !Now open differences file
    IF
	.MASTER_IOB[IOB$V_SEQUENCED] OR
	.INPUT_IOB[IOB$V_SEQUENCED]
    THEN
	STS=$STEP_OPEN(IOB=OUTPUT_IOB,FILE_SPEC=(.LGTO,.STRO),OPTIONS=OUTPUT,ATTRIBUTES=SEQUENCED,FAILURE=0)
    ELSE
	STS=$STEP_OPEN(IOB=OUTPUT_IOB,FILE_SPEC=(.LGTO,.STRO),OPTIONS=OUTPUT,FAILURE=0);
    IF
	NOT .STS
    THEN
	BADXPO(.STS,CAT(('Cannot open output file '),(.LGTO,.STRO)));

    !Set up the starting output sequence number
    OUTPUT_IOB[IOB$G_SEQ_NUMB]=0;

    O_OPN=TRUE;

    !Initialize comparison algorithm and fill the buffer
    CMPINI(FALSE,0,GET_CUR_MST,OUTDIFF,GET_LIN);

    OUTINI(OUTPUT_IOB);

    !No conflicts or merges so far
    CONFLICT=0;
    cant_res=false;
    MRG_CNT=0;

    TRUE

    END;				!End of SETUP
ROUTINE TERMINATE : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Clean up the loose ends and go away.
!
! FORMAL PARAMETERS:
!
!	NONE.
!
! IMPLICIT INPUTS:
!
!	All of the logical unit numbers of open files.
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	NONE.
!
! SIDE EFFECTS:
!
!	All of the files are closed.
!
!--

    BEGIN

    IF
	.I_OPN
    THEN
	BEGIN
	$step_close(IOB=INPUT_IOB,OPTIONS=REMEMBER);
	$STEP_DELETE(IOB=INPUT_IOB)
	END;

    IF
	.M_OPN
    THEN
	BEGIN
	$step_close(IOB=MASTER_IOB,OPTIONS=REMEMBER);
	$STEP_DELETE(IOB=MASTER_IOB)
	END;

!Only close output if chronology is not desired

    IF
	.O_OPN AND NOT (.CHRONO AND .CHRLEN NEQ 0 )
    THEN
    	BEGIN
        IF
    	    VERNUM( OUTPUT_IOB[IOB$T_RESULTANT] ) GTR 1
        THEN
    	    BEGIN
    	    FETSTS = s_isthere;
            sysmsg(s_isthere,CAT((.OUTFIL_LEN, .OUTFIL_PTR),
		   %string(' already exists, so the next ',
			%if VaxVms %then 'version', %fi
			%if Tops20 %then 'file generation', %fi
			' has been created')),0) ;
    	    END;
	$step_close(IOB=OUTPUT_IOB);
    	END ;

    END;				!End of TERMINATE
ROUTINE TEST_CONF (M_LINE,V_LINE) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Compare two blocks of text for generation replacement conflict.
!	A conflict exists where two blocks of text, both descendants of
!	the common ancestor replace the common ancestor.
!
! FORMAL PARAMETERS:
!
!	M_LINE - source line pointer
!	V_LINE - variation line pointer
!
! IMPLICIT INPUTS:
!
!	LIN_MST
!	LIN_VAR
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	GEN_CONF - changes conflict
!	GEN_MST - source changes are to be used
!	GEN_VAR - variation changes are to be used
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	L_PTR,
	L_SIZ,
	L_TMP,
	M_CTR,
	M_DEL,
	MST_DESC,
	V_CTR,
	V_DEL,
	VAR_DESC;

    !Automatic conflict if either operand is a no-op
    IF
	.M_LINE EQL -1 OR
	.V_LINE EQL -1
    THEN
	RETURN GEN_CONF;

    !Set both as not descendants
    MST_DESC=FALSE;
    VAR_DESC=FALSE;

    !There is no conflict if the two blocks have identical text
    V_CTR=.LIN_VAR;
    M_CTR=.LIN_MST;

    !Assume only deletions will occur for now
    M_DEL=TRUE;
    V_DEL=TRUE;

    !Now see if the two texts have the identical effect
    REPEAT
	BEGIN

	LOCAL
	    L1_LEN,
	    L1_PTR,
	    L2_LEN,
	    L2_PTR,
	    TMP_CHR;

	L1_PTR=0;
	L2_PTR=0;

	!Get pointer to text of first line
	WHILE
	    .M_CTR LSS .M_LINE
	DO
	    BEGIN
	    L1_PTR=.MST_PTR[.M_CTR-.LIN_MST];
	    L1_LEN=GET_STG_CT(L1_PTR);
	    M_CTR=.M_CTR+1;
	    !Skip sequence field, if any
	    IF
		.MASTER_IOB[IOB$V_SEQUENCED]
	    THEN
		BEGIN
		DO
		    L1_LEN=.L1_LEN-1
		UNTIL
		    CH$RCHAR_A(L1_PTR) EQL %C';';
		IF
		    .L1_LEN LSS 0
		THEN
		    BUG(LIT('Illegal master sequence field (TEST_CONF)'))
		END;

	    TMP_CHR=CH$RCHAR(.L1_PTR);
	    !Skip over generation number field
	    DO L1_LEN=.L1_LEN-1 UNTIL CH$RCHAR_A(L1_PTR) EQL %C'	';
	    !Stop searching when a real line is seen
	    IF
		.TMP_CHR NEQ %C'*'
	    THEN
		BEGIN
		M_DEL=FALSE;
		EXITLOOP
		END
	    END;

	!Get pointer to text of second line
	WHILE
	    .V_CTR LSS .V_LINE
	DO
	    BEGIN
	    L2_PTR=.VAR_PTR[.V_CTR-.LIN_VAR];
	    L2_LEN=GET_STG_CT(L2_PTR);
	    V_CTR=.V_CTR+1;
	    !Skip sequence field, if any
	    IF
		.INPUT_IOB[IOB$V_SEQUENCED]
	    THEN
		BEGIN
		DO
		    L2_LEN=.L2_LEN-1
		UNTIL
		    CH$RCHAR_A(L2_PTR) EQL %C';';
		IF
		    .L2_LEN LSS 0
		THEN
		    BUG(LIT('Illegal variation sequence field (TEST_CONF)'))
		END;

	    TMP_CHR=CH$RCHAR(.L2_PTR);
	    !Skip over generation number field
	    DO L2_LEN=.L2_LEN-1 UNTIL CH$RCHAR_A(L2_PTR) EQL %C'	';
	    !Quit searching when a real text line is seen
	    IF
		.TMP_CHR NEQ %C'*'
	    THEN
		BEGIN
		V_DEL=FALSE;
		EXITLOOP
		END
	    END;

	!Go away if matching deletions only
	IF
	    .M_CTR GEQ .M_LINE AND
	    .V_CTR GEQ .V_LINE AND
	    .M_DEL AND
	    .V_DEL
	THEN
	    !Use master lines and exit
	    RETURN GEN_MST;

	!No match if textual mismatch
	IF
	    .L1_PTR EQL 0 OR
	    .L2_PTR EQL 0
	THEN
	    EXITLOOP;
	IF
	    CH$NEQ(.L1_LEN,.L1_PTR,.L2_LEN,.L2_PTR)
	THEN
	    EXITLOOP;

	!Go away if everything has matched
	IF
	    .M_CTR GEQ .M_LINE AND
	    .V_CTR GEQ .V_LINE
	THEN
	    RETURN GEN_MST;

	!Exit loop if either text has finished first
	IF
	    .M_CTR GEQ .M_LINE OR
	    .V_CTR GEQ .V_LINE
	THEN
	    EXITLOOP

	END;

    !See if the master is a descendant or not
    INCR I FROM .LIN_MST TO .M_LINE-1 DO
	BEGIN
	L_PTR=.MST_PTR[.I-.LIN_MST];
	L_SIZ=GET_STG_CT(L_PTR);
	L_TMP=.L_PTR;

	!Skip sequence field
	IF
	    .MASTER_IOB[IOB$V_SEQUENCED]
	THEN
	    BEGIN
	    UNTIL
		CH$RCHAR_A(L_PTR) EQL %C';'
	    DO;
	    L_TMP=.L_PTR
	    END;

	!Get length of generation
	UNTIL
	    CH$RCHAR_A(L_TMP) EQL %C'	'
	DO;

	!Watch out for deletion mark
	IF
	    CH$RCHAR(.L_PTR) EQL %C'*'
	THEN
	    L_PTR=CH$PLUS(.L_PTR,1);

	IF
	    TEST_GEN(.L_PTR,CH$DIFF(.L_TMP,.L_PTR)-1)
	THEN
	    MST_DESC=TRUE
	END;

    !See if the variation is a descendant or not
    INCR I FROM .LIN_VAR TO .V_LINE-1 DO
	BEGIN
	L_PTR=.VAR_PTR[.I-.LIN_VAR];
	L_SIZ=GET_STG_CT(L_PTR);
	L_TMP=.L_PTR;

	!Skip sequence field
	IF
	    .INPUT_IOB[IOB$V_SEQUENCED]
	THEN
	    BEGIN
	    UNTIL
		CH$RCHAR_A(L_PTR) EQL %C';'
	    DO;
	    L_TMP=.L_PTR
	    END;

	!Get length of generation
	UNTIL
	    CH$RCHAR_A(L_TMP) EQL %C'	'
	DO;

	!Watch for deletion mark
	IF
	    CH$RCHAR(.L_PTR) EQL %C'*'
	THEN
	    L_PTR=CH$PLUS(.L_PTR,1);

	IF
	    TEST_GEN(.L_PTR,CH$DIFF(.L_TMP,.L_PTR)-1)
	THEN
	    !descendant
	    VAR_DESC=TRUE
	END;

    !Discover which text to use
    IF
	.MST_DESC AND
	.VAR_DESC
    THEN
	!Both appear to be descendants, conflict
	RETURN GEN_CONF;

    IF
	.MST_DESC
    THEN
	!The master text is the descendant, use it
	RETURN GEN_MST;

    IF
	.VAR_DESC
    THEN
	!The variation is the descendant, use it
	RETURN GEN_VAR;

    !Neither is the descendant, we probably are at a
    ! buffer boundary.

    !Check for one of the ranges being null
    if
	.m_line-.lin_mst gtr 0 and
	.v_line-.lin_var leq 0
    then
	!master is non-null, variation is null
	! so use the master
	return gen_mst;

    if
	.v_line-.lin_var gtr 0 and
	.m_line-.lin_mst leq 0
    then
	!variation is non-null, master is null
	! so use the variation
	return gen_var;

    !Can't resolve it so mark it as a conflict
    if
	not .cant_res
    then
	begin
	sysmsg(s_mrgerr,lit('Cannot resolve merge, marked as conflict'),0);
	cant_res=true
	end;

    gen_conf

    END;				!End of TEST_CONF
GLOBAL ROUTINE TEST_GEN (G1,G1_L) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	See if a generation is the descendant of the common ancestor in
!	COM_GEN
!
! FORMAL PARAMETERS:
!
!	G1 - pointer to generation in text
!	G1_L - length of generation in text
!
! IMPLICIT INPUTS:
!
!	COM_GEN - common ancestor generation
!	COM_G_LEN - String length of common ancestor
!
! IMPLICIT OUTPUTS:
!
!	NONE.
!
! ROUTINE VALUE:
! COMPLETION CODES:
!
!	TRUE - Generation is descendant
!	FALSE - Generation is not descendant
!
! SIDE EFFECTS:
!
!	NONE.
!
!--

    BEGIN

    LOCAL
	G1_CHR,
	G1_LGT,
	G1_PTR,
	G1_TMP,
	G1_VAL,
	C_CHR,
	C_LGT,
	C_PTR,
	C_TMP,
	C_VAL;

    !A null generation implies 1 and cannot be anyone's descendant.
    IF
	.G1_L EQL 0
    THEN
	RETURN FALSE;

    !Setup
    G1_PTR=.G1;
    G1_LGT=.G1_L;
    C_PTR=CH$PTR(COM_GEN);
    C_LGT=.COM_G_LEN;

    !Process entire generation expression
    REPEAT
	BEGIN

	!Get length of integer parts
	G1_TMP=G_NUM_LGT(.G1_PTR,.G1_LGT);
	C_TMP=G_NUM_LGT(.C_PTR,.C_LGT);

	!The lengths of both must be non-zero
	IF
	    .G1_TMP EQL 0 OR
	    .C_TMP EQL 0
	THEN
	    BUG(LIT('Illegal generation expression in TEST_GEN'));

	!Values
	G1_VAL=ASCDEC(G1_PTR,.G1_TMP);
	G1_LGT=.G1_LGT-.G1_TMP;
	C_VAL=ASCDEC(C_PTR,.C_TMP);
	C_LGT=.C_LGT-.C_TMP;

	IF
	    .G1_VAL EQL .C_VAL
	THEN
	    !Integer parts match
	    BEGIN

	    !Pick up which branch for G1
	    IF
		.G1_LGT NEQ 0
	    THEN
		BEGIN
		G1_CHR=CH$RCHAR_A(G1_PTR);
		G1_LGT=.G1_LGT-1
		END
	    ELSE
		G1_CHR=0;

	    !Pick up which branch for C
	    IF
		.C_LGT NEQ 0
	    THEN
		BEGIN
		C_CHR=CH$RCHAR_A(C_PTR);
		C_LGT=.C_LGT-1
		END
	    ELSE
		C_CHR=0;

	    !Failure if G1 precedes C
	    IF
		.G1_CHR EQL 0 AND
		.C_CHR NEQ 0
	    THEN
		RETURN FALSE;

	    !Success if C precedes G1
	    IF
		.C_CHR EQL 0 AND
		.G1_CHR NEQ 0
	    THEN
		RETURN TRUE;

	    !No match if the branches are not the same
	    IF
		.G1_CHR NEQ .C_CHR
	    THEN
		RETURN FALSE;

	    !Error if nothing follows branch marker
	    IF
		.G1_LGT EQL 0 AND
		.C_LGT EQL 0 AND
		.G1_CHR NEQ 0 AND
		.C_CHR NEQ 0
	    THEN
		!Error, illegal expression
		BUG(LIT('Illegal generation expression in TEST_GEN'))

	    END
	ELSE
	    BEGIN

	    IF
		.G1_VAL GTR .C_VAL
	    THEN
		!G1 is descendant of C
		RETURN TRUE;

	    !Can't possibly match
	    RETURN FALSE
	    END;

	!Identical generations, no descendant
	IF
	    .G1_LGT EQL 0 AND
	    .C_LGT EQL 0
	THEN
	    RETURN FALSE

	END

    END;				!End of TEST_GEN
END				!End of Module CMPMRG
ELUDOM