Google
 

Trailing-Edge - PDP-10 Archives - tops20-v7-ft-dist1-clock - 7-sources/scrupdate.bli
There are 10 other files named scrupdate.bli in the archive. Click here to see a list.
 %TITLE 'SCRUPDATE - update the screen'
MODULE SCRUPDATE (				! Update the screen
		IDENT = '3-003'			! File: SCRUPDATE.BLI Edit: CJG3003
		) =
BEGIN
!COPYRIGHT (c) DIGITAL EQUIPMENT CORPORATION 1981, 1988.  ALL RIGHTS RESERVED.
!
!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 THAT IS NOT SUPPLIED BY DIGITAL.
!
!
!++
! FACILITY:	EDT -- The DEC Standard Editor
!
! ABSTRACT:
!
!	This module does a screen update.
!
! ENVIRONMENT:	Runs at any access mode - AST reentrant
!
! AUTHOR: Bob Kushlis, CREATION DATE: September 8, 1979
!
! MODIFIED BY:
!
! 1-001	- Original.  DJS 12-Feb-1981.  This module was created by
!	extracting the routine EDT$$SC_UPD  from module SCREEN.
! 1-002	- Regularize headers.  JBS 13-Mar-1981
! 1-003	- Make sure the [EOB] test is valid when scrolling backwards.
!	   JBS 17-Sep-1981
! 1-004	- Revise autorepeat subroutine call.  JBS 30-Jan-1982
! 1-005	- Correct some spelling errors in comments.  JBS 02-Apr-1982
! 1-006	- Use new flag for scrolling logic.  JBS 02-Sep-1982
! 1-007 - Use the new screen structure and logic.  SMB 21-Sep-1982
! 1-008	- Remove unused external declaration of EDT$$FMT_LIT.  JBS 05-Oct-1982
! 1-009 - More debugging of screen scrolling and select.  SMB 08-Oct-1982
! 1-010	- Debug NOTRUNCATE mode.  JBS 12-Oct-1982
! 1-011 - Add insert and delete scrolling.  SMB 13-Oct-1982
! 1-012	- Clear RECS_INSERTED.  JBS 21-Oct-1982
! 1-013 - Scrolling debugging.  SMB 21-Oct-1982
! 1-014	- Move the code for marking select changes for repaint.  JBS 23-Oct-1982
! 1-015	- Simplify the logic that repaints the old screen.  JBS 24-Oct-1982
! 1-016	- Make sure all lines off the screen are marked for repaint, and
!	   support non-scrolling-region terminals.  JBS 24-Oct-1982
! 1-017	- Fix a performance problem with deselecting.  JBS 24-Oct-1982
! 1-018	- Watch out for deleted lines when updating the old screen.  JBS 24-Oct-1982
! 1-019	- Create UPDATE_LINE, so we can add fancy screen stuff for inserted and
!	   deleted lines.  JBS 23-Oct-1982
! 1-021 - Add scrolling to inset and delete line code.  SMB 25-Oct-1982
! 1-022 - Fix scrolling bug - add more notruncate code.  SMB 27-Oct-1982
! 1-023	- If we delete the top line, make the next line top.  JBS 01-Nov-1982
! 1-024	- Don't lose the line number if we must repaint but need not rebuild
!	   the screen data base.  JBS 01-Nov-1982
! 1-025	- Add the call to EDT$$FIX_NOTRUNC.  JBS 01-Nov-1982
! 1-026	- Fix a problem scrolling up on a small screen.  JBS 02-Nov-1982
! 1-027	- Speed up deselecting.  JBS 09-Nov-1982
! 1-028	- Rearrange select range processing.  JBS 10-Nov-1982
! 1-029	- Watch out for deleting the last line of the screen.  JBS 11-Nov-1982
! 1-030	- Recover from running out of memory.  JBS 15-Nov-1982
! 1-031 - Fix bug with cuts on noscroll terminal.  SMB 16-Nov-1982
! 1-032 - Fix notruncate bugs.  SMB 23-Nov-1982
! 1-033	- Worry about deleted lines.  JBS 25-Nov-1982
! 1-034	- Make a few efficiency improvements.  JBS 02-Dec-1982
! 1-035 - Add two paramaters to the SC_LNINS routine.  SMB 03-Dec-1982
! 1-036 - Change calculation of distance to select line. STS 07-Dec-1982
! 1-037	- When scrolling down, if we do not have scrolling regions
!	   erase the line that should have scrolled out of view.  JBS 14-Dec-1982
! 1-038 - Fix small bugs with boundary conditions.  SMB 20-Dec-1982
! 1-039	- Remove the edit buffer.  JBS 27-Dec-1982
! 1-040	- Do less repainting on select.  JBS 27-Dec-1982
! 1-041	- Add a missing dot in edit 1-040.  JBS 28-Dec-1982
! 1-042	- Collapse inserts and deletes together.  JBS 28-Dec-1982
! 1-043	- Add more TOP logic, to recover from rebuilds better.  JBS 29-Dec-1982
! 1-044	- Fix a bug that caused unnecessary rebuilding in NOTRUNCATE mode.  JBS 30-Dec-1982
! 1-045 - Modify setting of scrolling regions for multiple inserts.  SMB 30-Dec-1982
! 1-046 - Bug fixes on setting of top and more multiple insert work.  SMB 05-Jan-198f
! 1-047 - Fix bugs introduced in edit 046.  SMB 11-Jan-1983
! 1-048 - Bug fixes for "moving window" problems on deletes.  SMB 14-Jan-1983
! 1-049	- Worry about deleting the only line in the buffer.  JBS 18-Jan-1983
! 1-050	- Fix painting select regions on continuation lines.  JBS 19-Jan-1983
! 1-051	- Be more cautious about using the old cursor line after a rebuild.  JBS 20-Jan-1983
! 1-052 - Fix scrolling problems for NOSCROLL terminals.  SMB 25-Jan-1983
! 1-053 - Repair backwards scrolling bug introduced by edit 1-052.  SMB 26-Jan-1983
! 1-054	- We were updating the screen wrong if all of the following happened:
!	   1) we reset the screen, 2) we show the current position, and 3) we
!	   must jump to, rather than scroll to, the new position.  In showing
!	   the new position we should not assume that the screen is still erased.  JBS 28-Jan-1983
! 1-055	- Fix unreversing of backward select ranges.  JBS 28-Jan-1983
! 1-056 - Fix VT52 erase to end of screen bug with messages.  SMB 01-Feb-1983
! 1-057 - Avoid excess repainting after a CUT that crosses a line boundry.  JBS 25-Feb-1983
! 1-058	- Don't initialize the screen so often.  JBS 02-Mar-1983
! 1-059	- Mark the select region better on continued lines.  JBS 07-Mar-1983
! 3-001 - Add updates from V3 sources. GB 03-May-1983
! 3-002 - Fix translation bug in TOP command. CJG 6-Oct-1983
! 3-003 - Modify ASSERT macro to include error code. CJG 30-Jan-1984
!--
%SBTTL 'Declarations'
!
! TABLE OF CONTENTS:
!

REQUIRE 'EDTSRC:TRAROUNAM';

FORWARD ROUTINE
    EDT$$SC_UPD : NOVALUE,
    DELETE_LINE,
    INSERT_LINE;

!
! INCLUDE FILES:
!

REQUIRE 'EDTSRC:EDTREQ';

!
! MACROS:
!
!	NONE
!
! EQUATED SYMBOLS:
!
!	NONE
!
! OWN STORAGE:
!
!	NONE
!
! EXTERNAL REFERENCES:
!
!	In the routine
%SBTTL 'EDT$$SC_UPD  - update the screen'

GLOBAL ROUTINE EDT$$SC_UPD 			! Update the screen
    : NOVALUE =

!++
! FUNCTIONAL DESCRIPTION:
!
!	This routine is called to do a screen update.  Most of the work done
!	by this routine involves deciding on whether or not scrolling should
!	be done.  Basically, it figures out which line should be on the top
!	of the screen, then determines how far away from the current line it
!	has moved.  The actual update is handled by the EDT$$SC_RFRELN routine.
!
! FORMAL PARAMETERS:
!
!	NONE
!
! IMPLICIT INPUTS:
!
!	OLD_SEL
!	LNO_EMPTY
!	SCR_REBUILD
!	EOB_SCRPTR
!	SCR_CHGD
!	LN_BUF
!	LST_SCRPTR
!	CUR_SCRPTR
!	WK_LN
!	EOB_LN
!	SCR_BUF
!	FST_SCRPTR
!	CS_CHNO
!	CS_OLDCHNO
!	CS_LN
!	CS_LNO
!	CUR_COL
!	LN_NO
!	SEL_BUF
!	TOP_LN
!	CUR_BUF
!	SCR_LNS
!	SCLL_TOP
!	SCLL_BOT
!	TI_TYP
!	LN_PTR
!	TI_SCROLL
!	CSR_SCRPTR
!	TOP_SCRPTR
!	BOT_SCRPTR
!	CUR_SCRLN
!	FST_AVLN
!	TRUN
!	RECS_INSERTED
!	BOT_LINE
!
! IMPLICIT OUTPUTS:
!
!	OLD_SEL
!	SCR_REBUILD
!	CSR_SCRPTR
!	TOP_SCRPTR
!	CUR_SCRLN
!	SEL_BUF
!	CS_CHNO
!	CS_OLDCHNO
!	CS_LN
!	CS_LNO
!	LN_NO
!	TOP_LN
!	CUR_COL
!	RECS_INSERTED
!	FST_AVLN
!	BOT_SCRPTR
!	MEM_CNT
!	BOT_LINE
!
! ROUTINE VALUE:
!
!	NONE
!
! SIDE EFFECTS:
!
!	MANY
!
!--

    BEGIN

    EXTERNAL ROUTINE
	EDT$$CMP_LNO,			! Compare line numbers
	EDT$$SC_SETSCLLREG,		! Set the scrolling region
	EDT$$SC_LNINS,			! Insert a record into the screen data base
	EDT$$FMT_LIT,			! Output a literal string
	EDT$$SC_FNDREC,			! Find the current screen pointer
	EDT$$OUT_FMTBUF,		! Output the format buffer to the screen
	EDT$$RPL_CHGDLN,		! Replace a modified line in the work file
	EDT$$SC_INIT,			! Initialize the screen
	EDT$$SC_CPUCSPOS : NOVALUE,	! Compute the cursor position
	EDT$$SC_POSCSIF : NOVALUE,	! Position the cursor
	EDT$$SC_ERAALL : NOVALUE,	! Erase the screen
	EDT$$SC_MOVTOLN,		! Move to a record in the work file relative to the current record
	EDT$$SC_RFRELN : NOVALUE,	! Refresh a screen lint
	EDT$$SC_NONREVID : NOVALUE,	! Put the screen in normal video mode
	EDT$$SC_REPAINT : NOVALUE,	! Mark some lines in the screen data base for repaint
	EDT$$TI_ENBLAUTREP : NOVALUE,	! Enable or disable autorepeat
	EDT$$FIX_NOTRUNC : NOVALUE;	! Fix screen data base in NOTRUNCATE mode

    EXTERNAL
	BOT_SCRPTR : REF SCREEN_LINE,	! Address of bottom screen line
	OLD_SEL,			! Address of old select buffer
	LNO_EMPTY : LN_BLOCK,		! Code for empty line
	SCR_REBUILD,			! Rebuild the screen
	EOB_SCRPTR : REF SCREEN_LINE,	! EOB screen pointer
	SCR_CHGD,			! non-zero = the screen has been mangled
	MESSAGE_LINE,			! Message line
	LN_BUF,				! Start of line buffer
	CSR_SCRPTR : REF SCREEN_LINE,	! Current cursor line screen info
	CUR_SCRPTR : REF SCREEN_LINE,	! Current workfile line screen pointer
	LST_SCRPTR : REF SCREEN_LINE,	! Last data structure pointer
	WK_LN : REF LIN_BLOCK,		! Pointer to current line in work file
	EOB_LN,				! Special structure for [EOB] line
	SCR_BUF : REF TBCB_BLOCK,	! Current screen buffer
	FST_SCRPTR : REF SCREEN_LINE,	! First screen line info address
	TOP_SCRPTR : REF SCREEN_LINE,	! Top screen line info address
	CUR_SCRLN : LN_BLOCK,		! Current screen line record number
	CS_CHNO,			! character position of cursor
	CS_OLDCHNO,			! Previous character position of cursor
	CS_LN : LN_BLOCK,		! record number of cursor line
	CS_LNO,				! current cursor line
	CUR_COL,			! current cursor column
	LN_NO,				! current line number.
	SEL_POS,			! select character position
	SEL_LN : LN_BLOCK,		! select record
	SEL_BUF,			! select buffer.
	TOP_LN : LN_BLOCK,		! Line number of enforced top line.
	CUR_BUF : REF TBCB_BLOCK,	! The current buffer tbcb.
	SCR_LNS,			! No of lines on screen
	SCLL_TOP,			! Top line for scrolling up
	SCLL_BOT,			! Bottom line for scrolling down
	TI_TYP,				! Terminal type.
	LN_PTR,				! Current character pointer.
	TI_SCROLL,			! 1 = we have scrolling regions
	RECS_INSERTED,			! Number of records inserted since the last screen update
	FST_AVLN : REF SCREEN_LINE,	! List of available screen line data blocks
	TRUN,				! 0 = SET NOTRUNCATE
	MEM_CNT,			! Number of lines in the screen data base
	LNO0,				! Line number of 1
	BOT_LINE;			! All lines below this one have been erased

    LOCAL
	DOLOOPS,			! Code bypass flag
	TOP_DIST,			! Displacement to top scrptr
	TEMP_LINE : LN_BLOCK,		! Temp line number
	TOP_DISP,			! Top line displacement from current
	DIR,				! Direction of motion since last screen update
	SCLL_NUM,			! Scroll line limit
	TOP_SET,			! Top record successfully set
	DISP,				! Displacement from cursor screen line
	ABOVE,				! Number of lines above current
	BUILD_SCR,			! Flag which says rebuild screen
	SCRPTR : REF SCREEN_LINE,	! Address of a current screen line buffer
	CURSOR_POS,			! Column position of cursor
	CURSOR_LINE,			! Number of screen lines before cursor.
	BELOW,				! No. of screen lines below cursor line.
	REC_NO,				! Current relative reocrd number
	OLD_TOP_RECNO,			! Rel record number of old top record
	OLD_BOT_RECNO,			! Rel record number of old bottom record
	TOP_RECNO,			! Rel record number of new top record
	TOP_PTR : REF SCREEN_LINE,	! Address of the top line on the screen
	ERASE_ALL,			! 1 = we have erased the text part of the screen
	LNINS_VAL;			! Value returned by EDT$$SC_LNINS

!+
! Make sure we are in normal video if no select range.
!-

    IF (.SEL_BUF NEQA .CUR_BUF) THEN EDT$$SC_NONREVID ();

!+
! Remember the original character position and relative line number in
! work file terms.
!-
    LN_NO = 0;
    CS_CHNO = CH$DIFF (.LN_PTR, CH$PTR (LN_BUF,, BYTE_SIZE));
    MOVELINE (CUR_BUF [TBCB_CUR_LIN], CS_LN);
    EDT$$RPL_CHGDLN ();
!+
! If we are in NOTRUNCATE mode, make sure lines get adjusted due to carry from
! or borrow to earlier lines.
!-

    IF ( NOT .TRUN) THEN EDT$$FIX_NOTRUNC ();

    SCRPTR = 0;
!+
! Compute the cursor position.  We will recompute if we must rebuild the screen data base.
!-
    EDT$$SC_CPUCSPOS (CURSOR_LINE, CURSOR_POS);
    CURSOR_LINE = .CS_LNO;
!+
! If the screen has been mangled, or we have changed buffers, erase the screen and
! repaint all the lines.
!-

    IF ((.SCR_CHGD NEQ 0) OR (.SCR_BUF NEQA .CUR_BUF))
    THEN
	BEGIN
!+
! Don't initialize the terminal unless it has been requested.
!-

	IF (.SCR_CHGD EQL 2) THEN EDT$$SC_INIT ();

!+
! Erase the screen.
!-
	CS_LNO = 0;
	EDT$$SC_ERAALL ();
	BOT_LINE = 0;
	ERASE_ALL = 1;
	END
    ELSE
	ERASE_ALL = 0;

!+
! Determine whether the screen structure has to be rebuilt.
!-
    BUILD_SCR = .SCR_REBUILD;
!+
! If the current position is not in the screen data base, rebuild.
!-

    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN
	CUR_SCRPTR = EDT$$SC_FNDREC (CH$DIFF (.LN_PTR, CH$PTR (LN_BUF,, BYTE_SIZE)), DISP);

	IF ((.CUR_SCRPTR EQLA 0) OR (.TOP_SCRPTR [SCR_NXT_LINE] EQLA 0)) THEN BUILD_SCR = 1;

	END;

!+
! Compute the direction of motion since the last screen update.
! If we have changed buffers, assume forward.
!-

    IF ((EDT$$CMP_LNO (LNO_EMPTY, CUR_SCRLN) EQL 0) OR (.SCR_BUF NEQA .CUR_BUF))
    THEN
	DIR = 1
    ELSE
	DIR = EDT$$CMP_LNO (CS_LN, CUR_SCRLN);

    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN

	IF ((.SEL_BUF NEQA .OLD_SEL) AND (.TI_TYP EQL TERM_VT100))
	THEN
	    BEGIN
!+
! We have started or ended a selection.  Repaint all selected or formerly selected lines.
!-

	    LOCAL
		CHAR_NO,
		SELDIR,
		REC_OFFSET,
		OUR_LINE : LN_BLOCK,
		OUR_CHNO,
		OUR_SCRPTR : REF SCREEN_LINE;

!+
! If this is a deselection we must repaint from the old line to the select line.
! If this is a selection we must repaint from the current line to the select line.
!-

	    IF (.SEL_BUF EQLA 0)
	    THEN
		BEGIN
		MOVELINE (CUR_SCRLN, OUR_LINE);
		SUBLINE (CUR_SCRLN, CS_LN, TEMP_LINE);
		REC_OFFSET = .(TEMP_LINE [LN_LO])<0, 18, 1>;
		OUR_CHNO = .CS_OLDCHNO;
		OUR_SCRPTR = .CSR_SCRPTR;
		END
	    ELSE
		BEGIN
		MOVELINE (CS_LN, OUR_LINE);
		REC_OFFSET = 0;
		OUR_CHNO = .CS_CHNO;
		OUR_SCRPTR = .CUR_SCRPTR;
		END;

	    SUBLINE (OUR_LINE, SEL_LN, TEMP_LINE);

	    IF ((.TEMP_LINE [LN_HI] AND %O'400000') NEQ 0)
	    THEN
		SELDIR = -1
	    ELSE

		IF (.TEMP_LINE [LN_LO] NEQU 0) THEN SELDIR = 1 ELSE SELDIR = 0;

	    REC_NO = .(TEMP_LINE [LN_LO])<0, 18, 1> - .REC_OFFSET;
	    EDT$$SC_MOVTOLN (.REC_NO);
	    SCRPTR = EDT$$SC_FNDREC (CH$DIFF (.SEL_POS, CH$PTR (LN_BUF,, BYTE_SIZE)), DISP);

	    IF (.SCRPTR EQLA 0)
	    THEN
		BUILD_SCR = 1
	    ELSE
		BEGIN

		CHAR_NO = CH$DIFF (.SEL_POS, CH$PTR (LN_BUF,, BYTE_SIZE));
		IF (.SELDIR EQL 0)
		THEN
		    BEGIN

		    IF (.CHAR_NO LSS .OUR_CHNO)	!
		    THEN
			EDT$$SC_REPAINT (.SCRPTR, 	!
			    .OUR_SCRPTR, 	!
			    .CHAR_NO - .SCRPTR [SCR_CHR_FROM],
			    .OUR_CHNO - .OUR_SCRPTR [SCR_CHR_FROM] - 1, 0)
		    ELSE

			IF (.CHAR_NO GTR .OUR_CHNO)	!
			THEN
			    EDT$$SC_REPAINT (.OUR_SCRPTR, 	!
				.SCRPTR, 	!
				.OUR_CHNO - .OUR_SCRPTR [SCR_CHR_FROM], 	!
				.CHAR_NO - .SCRPTR [SCR_CHR_FROM] - 1, 0);

		    END
		ELSE

		    IF (.SELDIR GTR 0)
		    THEN
			EDT$$SC_REPAINT (.OUR_SCRPTR, 	!
			    .SCRPTR, 		!
			    .OUR_CHNO - .OUR_SCRPTR [SCR_CHR_FROM], 	!
			    .CHAR_NO - .SCRPTR [SCR_CHR_FROM] - 1, 0)
		    ELSE

			IF (.SELDIR LSS 0)
			THEN
			    EDT$$SC_REPAINT (.SCRPTR, 	!
				.OUR_SCRPTR, 	!
				.CHAR_NO - .SCRPTR [SCR_CHR_FROM], 	!
				.OUR_CHNO - .OUR_SCRPTR [SCR_CHR_FROM] - 1, 0)
			ELSE
			    ASSERT (22, 0);

		END;
	    END;
	END;


    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN

	IF ((.SEL_BUF EQLA .CUR_BUF) AND (.TI_TYP EQL TERM_VT100))
	THEN
	    BEGIN
!+
! The select range is in the current buffer.  Repaint lines between the previous
! and the current cursor, to be sure they are properly reversed or not.
!-

	    IF (.DIR LSS 0)
	    THEN
		EDT$$SC_REPAINT (.CUR_SCRPTR, .CSR_SCRPTR,
		    .CS_CHNO - .CUR_SCRPTR [SCR_CHR_FROM],
		    .CS_OLDCHNO - .CSR_SCRPTR [SCR_CHR_FROM] - 1, 0)
	    ELSE

		IF (.DIR GTR 0)
		THEN
		    EDT$$SC_REPAINT (.CSR_SCRPTR, .CUR_SCRPTR,
			.CS_OLDCHNO - .CSR_SCRPTR [SCR_CHR_FROM], 	!
			.CS_CHNO - .CUR_SCRPTR [SCR_CHR_FROM] - 1, 0)
		ELSE

		    IF (.CS_CHNO LSS .CS_OLDCHNO)	!
		    THEN
			EDT$$SC_REPAINT (.CUR_SCRPTR, 	!
			    .CSR_SCRPTR, 	!
			    .CS_CHNO - .CUR_SCRPTR [SCR_CHR_FROM],
			    .CS_OLDCHNO - .CSR_SCRPTR [SCR_CHR_FROM] - 1, 0)
		    ELSE

			IF (.CS_CHNO GTR .CS_OLDCHNO)	!
			THEN
			    EDT$$SC_REPAINT (.CSR_SCRPTR, 	!
				.CUR_SCRPTR, 	!
				.CS_OLDCHNO - .CSR_SCRPTR [SCR_CHR_FROM], 	!
				.CS_CHNO - .CUR_SCRPTR [SCR_CHR_FROM] - 1, 0);

	    END;

	END;

!+
! Mark all lines off the screen for repaint.
!-

    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN
!+
! If the screen has been erased we must repaint everything, otherwise only lines
! off the screen will need to be repainted.  Marking the lines off the screen for
! repaint removes the deleted lines from the screen data base, to avoid confusing
! our count of the number of lines above and below the current line.
!-

	IF .ERASE_ALL
	THEN
	    EDT$$SC_REPAINT (.FST_SCRPTR, .LST_SCRPTR, 0, 255, 1)
	ELSE
	    BEGIN

	    IF (.RECS_INSERTED GTR 0)
	    THEN
		BEGIN

		IF (.TOP_SCRPTR NEQA 0)
		THEN
		    BEGIN
		    SCRPTR = .TOP_SCRPTR [SCR_PRV_LINE];

		    IF (.SCRPTR NEQA 0) THEN EDT$$SC_REPAINT (.FST_SCRPTR, .SCRPTR, 0, 255, 1);

		    END;

		IF (.BOT_SCRPTR NEQA 0)
		THEN
		    BEGIN
		    SCRPTR = .BOT_SCRPTR [SCR_NXT_LINE];

		    IF (.SCRPTR NEQA 0) THEN EDT$$SC_REPAINT (.SCRPTR, .LST_SCRPTR, 0, 255, 1);

		    END;

		END;

	    END;

	END;

!+
! If we have lost our record of the top of the screen we must rebuild.
!-

    IF (.TOP_SCRPTR EQLA 0) THEN BUILD_SCR = 1;

    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN
!+
! Find the relative record number of the old cursor line.
! We must be careful of deleted lines.  The convention is that a deleted line
! has the record number of the next lower line.  This prevents deleted
! lines before record zero from having negative absolute record numbers.
!-
	SCRPTR = .CUR_SCRPTR;
	REC_NO = 0;

	CASE .DIR FROM -1 TO 1 OF
	    SET

	    [1] :
		BEGIN
!+
! The new line is after the old.  We must move back in the work file.
!-

		DO
		    BEGIN

		    IF ((.SCRPTR [SCR_LINE_IDX] EQL 0) OR 	!
			((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0))
		    THEN
			BEGIN

			LOCAL
			    PREV_SCRPTR : REF SCREEN_LINE;

			PREV_SCRPTR = .SCRPTR [SCR_PRV_LINE];

			IF (.PREV_SCRPTR NEQA 0)
			THEN
			    BEGIN

			    IF ((.PREV_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0)
			    THEN
				REC_NO = .REC_NO - 1;

			    END;

			END;

		    SCRPTR = .SCRPTR [SCR_PRV_LINE];
		    END
		UNTIL ((.SCRPTR EQLA .CSR_SCRPTR) OR (.SCRPTR EQLA 0));

		END;

	    [0] :
		BEGIN
!+
! We are positioned correctly in the work file.
!-
		SCRPTR = .CSR_SCRPTR;
		END;

	    [-1] :
		BEGIN
!+
! The new line is before the old.  We must move forward in the work file.
!-

		DO
		    BEGIN

		    LOCAL
			NEXT_SCRPTR : REF SCREEN_LINE;

		    NEXT_SCRPTR = .SCRPTR [SCR_NXT_LINE];

		    IF (.NEXT_SCRPTR NEQA 0)
		    THEN
			BEGIN

			IF (((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0) AND 	!
			    ((.NEXT_SCRPTR [SCR_LINE_IDX] EQL 0) OR 	!
			    ((.NEXT_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0)))
			THEN
			    REC_NO = .REC_NO + 1;

			END;

		    SCRPTR = .SCRPTR [SCR_NXT_LINE];
		    END
		UNTIL ((.SCRPTR EQLA .CSR_SCRPTR) OR (.SCRPTR EQLA 0));

		END;

	    [OUTRANGE] :
		ASSERT (11, 0);
	    TES;

!+
! If we couldn't find it, rebuild the screen.
!-

	IF (.SCRPTR NEQA .CSR_SCRPTR) THEN BUILD_SCR = 1;

	END;

    IF ( NOT .BUILD_SCR)
    THEN
	BEGIN
!+
! Now work backwards to the old top line.
!-

	WHILE ((.SCRPTR NEQA .TOP_SCRPTR) AND (.SCRPTR NEQA 0)) DO
	    BEGIN

	    IF ((.SCRPTR [SCR_LINE_IDX] EQL 0) OR 	!
		((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0))
	    THEN
		BEGIN

		LOCAL
		    PREV_SCRPTR : REF SCREEN_LINE;

		PREV_SCRPTR = .SCRPTR [SCR_PRV_LINE];

		IF (.PREV_SCRPTR NEQA 0)
		THEN
		    BEGIN

		    IF ((.PREV_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0) THEN REC_NO = .REC_NO - 1;

		    END;

		END;

	    SCRPTR = .SCRPTR [SCR_PRV_LINE];
	    END;

	OLD_TOP_RECNO = .REC_NO;
	END;

!+
! If we didn't find it, rebuild the screen data base.
!-

    IF (.SCRPTR NEQA .TOP_SCRPTR) THEN BUILD_SCR = 1;

    IF ( NOT .BUILD_SCR)
    THEN
!+
! Update the lines which are on the screen.
!-
	BEGIN

	LOCAL
	    UPDATE_DONE,
	    ANOTHER_PASS,
	    BEG_SCRPTR : REF SCREEN_LINE,
	    INS_COUNT,
	    PREV_INS_COUNT;

!+
! Check for regions containing an equal number of inserted and deleted lines.
! Avoid double scrolling (and scrolling lines off the screen then back on) by
! changing all inserted lines in such regions into modified lines, and freeing
! the deleted lines.
!-

	DO
	    BEGIN
	    ANOTHER_PASS = 0;
	    INS_COUNT = 0;
	    SCRPTR = .TOP_SCRPTR;

	    DO
		BEGIN
		UPDATE_DONE = 0;
		PREV_INS_COUNT = .INS_COUNT;

		IF ((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_INSLN) NEQ 0) THEN INS_COUNT = .INS_COUNT + 1;

		IF ((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0) THEN INS_COUNT = .INS_COUNT - 1;

		IF ((.INS_COUNT NEQ 0) AND (.PREV_INS_COUNT EQL 0)) THEN BEG_SCRPTR = .SCRPTR;

		IF ((.INS_COUNT EQL 0) AND (.PREV_INS_COUNT NEQ 0))
		THEN
		    BEGIN
!+
! Move the top line down, if it was deleted.
!-

		    IF (.BEG_SCRPTR EQLA .TOP_SCRPTR)
		    THEN

			WHILE ((.TOP_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0) DO
			    TOP_SCRPTR = .TOP_SCRPTR [SCR_NXT_LINE];

!+
! Free deleted lines and mark all other lines to be repainted.
!-
		    EDT$$SC_REPAINT (.BEG_SCRPTR, .SCRPTR, 0, 255, 1);
		    UPDATE_DONE = 1;
		    ANOTHER_PASS = 1;
		    END
		ELSE
		    BEGIN

		    IF (.SCRPTR EQLA .BOT_SCRPTR) OR (.SCRPTR [SCR_NXT_LINE] EQLA 0)
		    THEN
			UPDATE_DONE = 1
		    ELSE
			SCRPTR = .SCRPTR [SCR_NXT_LINE];

		    END;

		END
	    UNTIL .UPDATE_DONE;

!+
! The screen is no longer erased.  Subsequent lines painted must issue an "erase to end of line" to
! blank out the end of a completely painted line, except in special cases such as scrolling a line
! onto the screen.
!-
	    ERASE_ALL = 0;
	    END
	UNTIL ( NOT .ANOTHER_PASS);

!+
! Now repaint all the lines so marked, and do any residual inserts and deletes on the screen.
!-

	DO
	    BEGIN

	    LOCAL
		STATUS;				! Insert or Delete status

	    ANOTHER_PASS = 0;
	    REC_NO = .OLD_TOP_RECNO;
	    SCRPTR = .TOP_SCRPTR;
	    CS_LNO = 0;

	    DO
		BEGIN
		UPDATE_DONE = 0;

		IF ((.SCRPTR [SCR_EDIT_FLAGS] AND 	!
		    (SCR_EDIT_MODIFY OR SCR_EDIT_INSLN OR SCR_EDIT_DELLN)) NEQ 0)
		THEN
		    BEGIN
!+
! Is this a deleted line?
!-

		    IF ((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0)
		    THEN
			BEGIN
			STATUS = DELETE_LINE (.SCRPTR, .REC_NO, .ERASE_ALL, OLD_TOP_RECNO);
			END
		    ELSE

			IF ((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_INSLN) NEQ 0)
			THEN
			    BEGIN
			    STATUS = INSERT_LINE (.SCRPTR, .REC_NO, .ERASE_ALL, OLD_TOP_RECNO);
			    END
			ELSE
			    BEGIN
!+
! The line is neither inserted nor deleted.  Just paint it on the screen.
!-
			    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
			    EDT$$SC_RFRELN (.SCRPTR, .ERASE_ALL);
			    STATUS = 1;
			    END;

		    IF ( NOT .STATUS)
		    THEN
			BEGIN
			UPDATE_DONE = 1;
			ANOTHER_PASS = 1;
			END;

		    END;

		IF ( NOT .UPDATE_DONE)
		THEN
		    BEGIN
		    CS_LNO = .CS_LNO + 1;

		    IF (.CS_LNO EQL .SCR_LNS)
		    THEN
			UPDATE_DONE = 1
		    ELSE
			BEGIN

			IF (.SCRPTR [SCR_NXT_LINE] EQLA 0)
			THEN
			    BEGIN
!+
! We have run out of screen data base, but we have not yet filled the screen.  If we
! are at [EOB] that is OK, otherwise extend the screen data base.
!-

			    IF (.SCRPTR EQLA .EOB_SCRPTR)
			    THEN
				BEGIN
!+
! We have reached [EOB] before filling the screen.  This will be fixed by scrolling later,
! if that is possible.  Erase the rest of the screen unless the whole screen has been
! erased already.
!-

				IF (.CS_LNO LSS .BOT_LINE) THEN EDT$$SC_ERAALL ();

				UPDATE_DONE = 1
				END
			    ELSE
				BEGIN
!+
! We are not at [EOB].  Add another record to the screen data base, and keep
! painting the screen.
!-
				REC_NO = .REC_NO + 1;
				ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
				LNINS_VAL = EDT$$SC_LNINS (0, WK_LN [LIN_TEXT],
				    .WK_LN [LIN_LENGTH]);

				IF (.LNINS_VAL EQL 0)
				THEN
				    UPDATE_DONE = 1
				ELSE
				    BEGIN
				    SCRPTR = .SCRPTR;
				    ASSERT (23, .SCRPTR [SCR_NXT_LINE] NEQA 0);
				    SCRPTR = .SCRPTR [SCR_NXT_LINE];
				    ASSERT (23, .SCRPTR [SCR_LINE_IDX] EQL 0);
				    END;

				END;

			    END
			ELSE
			    BEGIN

			    LOCAL
				NEXT_SCRPTR : REF SCREEN_LINE;

			    NEXT_SCRPTR = .SCRPTR [SCR_NXT_LINE];

			    IF (.NEXT_SCRPTR NEQA 0)
			    THEN
				BEGIN

				IF (((.SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0) AND 	!
				    ((.NEXT_SCRPTR [SCR_LINE_IDX] EQL 0) OR 	!
				    ((.NEXT_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0)))
				THEN
				    REC_NO = .REC_NO + 1;

				END;

			    SCRPTR = .SCRPTR [SCR_NXT_LINE];
			    END;

			END;

		    END;

		END
	    UNTIL .UPDATE_DONE;

	    END
	UNTIL ( NOT .ANOTHER_PASS);

	EDT$$SC_SETSCLLREG (0, .SCR_LNS);
	BOT_LINE = .CS_LNO;
	OLD_BOT_RECNO = .REC_NO;
	BOT_SCRPTR = .SCRPTR;
	END;

    IF .BUILD_SCR
    THEN
	BEGIN
!+
! We must rebuild the screen data base.  Put all the screen line
! blocks on the free list.
!-

	IF (.FST_SCRPTR NEQA 0)
	THEN
	    BEGIN
	    LST_SCRPTR [SCR_NXT_LINE] = .FST_AVLN;
	    FST_AVLN = .FST_SCRPTR;
	    END;

	FST_SCRPTR = 0;
	LST_SCRPTR = 0;
	TOP_SCRPTR = 0;
	CUR_SCRPTR = 0;
	BOT_SCRPTR = 0;
	EOB_SCRPTR = 0;
	MEM_CNT = 0;
	END;

!+
! Align the cursor screen pointer with the current screen pointer.
!-
    REC_NO = 0;
    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
    SCR_BUF = .CUR_BUF;
    MOVELINE (CUR_BUF [TBCB_CUR_LIN], CUR_SCRLN);

    IF .BUILD_SCR
    THEN
	BEGIN
	EDT$$SC_LNINS (0, WK_LN [LIN_TEXT], .WK_LN [LIN_LENGTH]);
	CSR_SCRPTR = .FST_SCRPTR;

	IF (.TRUN EQL 0)			!
	THEN
	    CUR_SCRPTR = EDT$$SC_FNDREC (.CS_CHNO, DISP)
	ELSE
	    CUR_SCRPTR = .CSR_SCRPTR;

	END;

!+
! When we reach this point either the old screen has been updated
! or we will be rebuilding the screen data base.
! Determine which line should be at the top of the screen
!-
    SCRPTR = .CUR_SCRPTR;
    REC_NO = 0;
    BELOW = 0;
    ABOVE = 0;
!+
! Calculate the number of lines above and below the current line
! because we might have to move the cursor.  This may cause the screen
! data structure to be extended.
!-
    DOLOOPS = 0;

    IF ((.RECS_INSERTED GTR 0)		!
	OR (.CSR_SCRPTR NEQA .CUR_SCRPTR)	!
	OR (.BUILD_SCR)				!
	OR (EDT$$CMP_LNO (TOP_LN, LNO_EMPTY) NEQ 0))
    THEN
	BEGIN

	LOCAL
	    AT_BOTTOM;

	DOLOOPS = 1;
	AT_BOTTOM = 0;

	WHILE ((.BELOW LSS (.SCR_LNS*2)) AND ( NOT .AT_BOTTOM)) DO
	    BEGIN

	    IF (.SCRPTR EQLA 0)
	    THEN
		BEGIN
		ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
		LNINS_VAL = EDT$$SC_LNINS (0, WK_LN [LIN_TEXT], .WK_LN [LIN_LENGTH]);

		IF (.LNINS_VAL EQL 0)
		THEN
		    AT_BOTTOM = 1
		ELSE
		    BEGIN
		    BELOW = .BELOW + .LNINS_VAL;
		    REC_NO = .REC_NO + 1;

		    IF (.WK_LN EQLA EOB_LN)
		    THEN
			BEGIN
			EOB_SCRPTR = .LST_SCRPTR;
			AT_BOTTOM = 1;
			END;

		    END;

		END
	    ELSE
		BEGIN
		BELOW = .BELOW + 1;

		IF (.SCRPTR EQLA .EOB_SCRPTR)
		THEN
		    AT_BOTTOM = 1
		ELSE
		    BEGIN
		    SCRPTR = .SCRPTR [SCR_NXT_LINE];

		    IF (.SCRPTR EQLA 0)
		    THEN
			REC_NO = .REC_NO + 1
		    ELSE

			IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO + 1;

		    END;

		END;

	    END;

	END;

!+
! Now see how many lines are available above the current line.
!-
    SCRPTR = .CUR_SCRPTR;
    REC_NO = 0;

    IF (.DOLOOPS)
    THEN
	BEGIN
	BEGIN

	LOCAL
	    AT_TOP;

	AT_TOP = 0;

	WHILE ((.ABOVE LSS (.SCR_LNS*2)) AND ( NOT .AT_TOP)) DO
	    BEGIN

	    IF (.SCRPTR NEQA 0)
	    THEN
		BEGIN

		IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO - 1;

		SCRPTR = .SCRPTR [SCR_PRV_LINE];
		END;

!+
! If the screen data structure ends, try to add new items to the front of it.
!-

	    IF (.SCRPTR EQLA 0)
	    THEN
		BEGIN

		IF EDT$$SC_MOVTOLN (.REC_NO)
		THEN
		    BEGIN
		    LNINS_VAL = EDT$$SC_LNINS (.FST_SCRPTR, WK_LN [LIN_TEXT],
			.WK_LN [LIN_LENGTH]);

		    IF (.LNINS_VAL EQL 0)
		    THEN
			AT_TOP = 1
		    ELSE
			BEGIN
			ABOVE = .ABOVE + .LNINS_VAL;
			SCRPTR = .FST_SCRPTR;
			END;

		    END
		ELSE
		    AT_TOP = 1;

		END
	    ELSE
		ABOVE = .ABOVE + 1;

	    END;

	END;
	SCRPTR = .CUR_SCRPTR;
!+
! Now compute the top line.  If there is an enforced top line, we try to use it.
! If there is not, we try to use the old top line.  Otherwise we go up a number of
! lines depending on the direction of the last move, to preserve as much context
! as possible.
!-
	TOP_SET = 0;

	IF (EDT$$CMP_LNO (TOP_LN, LNO_EMPTY) NEQ 0)
	THEN
	    BEGIN
!+
! There is a request for a top line.  If it is below the current line, reject it.
!-

	    IF (EDT$$CMP_LNO (TOP_LN, CS_LN) GTR 0)
	    THEN
		MOVELINE (LNO_EMPTY, TOP_LN)
	    ELSE
		BEGIN
!+
! The requested top line is above or on the current line.  If it is too far above, reject it.
!-
		TOP_DIST = 0;
		SCRPTR = .CUR_SCRPTR;
		MOVELINE (CS_LN, TEMP_LINE);

		WHILE ((EDT$$CMP_LNO (TEMP_LINE, TOP_LN) NEQ 0) AND 	!
		    (.TOP_DIST LSS .SCLL_BOT) AND 	!
		    (.SCRPTR NEQA 0)) DO
		    BEGIN

		    IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN SUBLINE (LNO0, TEMP_LINE, TEMP_LINE);

		    SCRPTR = .SCRPTR [SCR_PRV_LINE];

		    IF (.SCRPTR NEQA 0) THEN TOP_DIST = .TOP_DIST + 1;

		    END;

!+
! If we found the line and it would not require [EOB] to be above the bottom
! of the screen, accept it.
!-

		IF ((EDT$$CMP_LNO (TEMP_LINE, TOP_LN) EQL 0) AND ((.BELOW + .TOP_DIST) GEQ .SCR_LNS))
		THEN
		    TOP_SET = 1
		ELSE
		    MOVELINE (LNO_EMPTY, TOP_LN);

		END;

	    END;

!+
! If we have no top determined yet, try to use the old top.
!-

	IF (( NOT .TOP_SET) AND (.TOP_SCRPTR NEQA 0))
	THEN
	    BEGIN
	    SCRPTR = .CUR_SCRPTR;
	    REC_NO = 0;
	    TOP_DIST = 0;

	    WHILE ((.TOP_DIST LEQ .SCLL_BOT) AND 	!
		(.SCRPTR NEQA .TOP_SCRPTR) AND 	!
		(.SCRPTR NEQA 0)) DO
		BEGIN

		IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO - 1;

		SCRPTR = .SCRPTR [SCR_PRV_LINE];

		IF (.SCRPTR NEQA 0) THEN TOP_DIST = .TOP_DIST + 1;

		END;

!+
! If we found the old top line and it will leave the cursor line in range
! and not put the [EOB] above the bottom of the screen, use it.
!-

	    IF ((.TOP_DIST LEQ .SCLL_BOT) AND 	!
		(.TOP_DIST GEQ .SCLL_TOP) AND 	!
		((.BELOW + .TOP_DIST) GEQ .SCR_LNS) AND 	!
		(.SCRPTR EQLA .TOP_SCRPTR))
	    THEN
		TOP_SET = 1;

	    END;

!+
! If top is still not set and there is a record of a previous cursor line
! and we are rebuilding the screen data base, try to compute the top line
! such that the cursor stays where it was.  This is useful in case the code
! for fixing notruncated lines must force a rebuild of the screen data base.
!-

	IF (( NOT .TOP_SET) AND .SCR_REBUILD AND (.CURSOR_LINE GEQ .SCLL_TOP) AND 	!
	    (.CURSOR_LINE LEQ .SCLL_BOT) AND ((.BELOW + .CURSOR_LINE) GEQ .SCR_LNS))
	THEN
	    BEGIN
	    SCRPTR = .CUR_SCRPTR;
	    TOP_DIST = -1;

	    WHILE ((.SCRPTR NEQA 0) AND (.TOP_DIST NEQ .CURSOR_LINE)) DO
		BEGIN
		SCRPTR = .SCRPTR [SCR_PRV_LINE];
		TOP_DIST = .TOP_DIST + 1;
		END;

	    IF (.TOP_DIST EQL .CURSOR_LINE) THEN TOP_SET = 1;

	    END;

!+
! If top is still not set, try to find a new top line a suitable distance
! above the current line.
!-

	IF ( NOT .TOP_SET)
	THEN
	    BEGIN
!+
! Work back until the beginning of the screen data structure or until TOP_DIST is
! big enough for the direction we are moving.
!-
!+
! The (.CURSOR_LINE + .RECS_INSERTED) code is here to fix a problem on VT52's
! with the screen scrolling too far up on a paste.
!-

	    IF ((.DIR GEQ 0) OR (((.CURSOR_LINE + .RECS_INSERTED) GTR .SCLL_BOT)	!
		AND (.RECS_INSERTED GTR 0)))
	    THEN
		SCLL_NUM = .SCLL_BOT
	    ELSE
		SCLL_NUM = .SCLL_TOP;

!+
! If necessary, work back further to avoid lifting the [EOB] above the last line
! of the screen.
!-
	    SCLL_NUM = MAX (.SCLL_NUM, .SCR_LNS - .BELOW);
!
	    REC_NO = 0;
	    SCRPTR = .CUR_SCRPTR;
	    TOP_DIST = -1;

	    WHILE ((.SCRPTR NEQA 0) AND (.TOP_DIST NEQ .SCLL_NUM)) DO
		BEGIN
		SCRPTR = .SCRPTR [SCR_PRV_LINE];
		TOP_DIST = .TOP_DIST + 1;
		END;

!+
! If we found the line we were looking for, accept it.
!-

	    IF (.TOP_DIST EQL .SCLL_NUM) THEN TOP_SET = 1;

	    END;

!+
! If no line is suitable, use the first line in the screen data base.  This can happen when we
! have a buffer that fits on the screen.
!-

	IF ( NOT .TOP_SET)
	THEN
	    BEGIN
	    TOP_DIST = -1;
	    SCRPTR = .CUR_SCRPTR;

	    WHILE (.SCRPTR NEQA 0) DO
		BEGIN
		TOP_DIST = .TOP_DIST + 1;
		SCRPTR = .SCRPTR [SCR_PRV_LINE];
		END;

	    END;

!+
! Now that TOP_DIST is computed, find the new top screen pointer.
!-
	SCRPTR = .CUR_SCRPTR;
	REC_NO = 0;

	INCR I FROM 1 TO .TOP_DIST DO
	    BEGIN

	    IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO - 1;

	    SCRPTR = .SCRPTR [SCR_PRV_LINE];
	    END;

	TOP_RECNO = .REC_NO;
	TOP_PTR = .SCRPTR;
!+
! Compute the number of lines between the old and new top lines,
! so we can see how far to scroll, and in which direction.
!-

	IF ((.TOP_SCRPTR NEQA 0) AND (.TOP_SCRPTR NEQA .TOP_PTR))
	THEN
	    BEGIN

	    LOCAL
		SEEN_OLD,
		SEEN_NEW;

	    SEEN_OLD = 0;
	    SEEN_NEW = 0;
	    SCLL_NUM = 0;
	    SCRPTR = .FST_SCRPTR;

	    WHILE ((.SCRPTR NEQA 0) AND ( NOT (.SEEN_OLD AND .SEEN_NEW))) DO
		BEGIN

		IF (.SEEN_OLD AND ( NOT .SEEN_NEW)) THEN SCLL_NUM = .SCLL_NUM + 1;

		IF (.SEEN_NEW AND ( NOT .SEEN_OLD)) THEN SCLL_NUM = .SCLL_NUM - 1;

		IF (.SCRPTR EQLA .TOP_PTR) THEN SEEN_NEW = 1;

		IF (.SCRPTR EQLA .TOP_SCRPTR) THEN SEEN_OLD = 1;

		SCRPTR = .SCRPTR [SCR_NXT_LINE];
		END;

	    ASSERT (23, .SEEN_NEW);
!+
! If the old top line is not in the data base, it must be too far away
! to scroll.
!-

	    IF ( NOT .SEEN_OLD) THEN SCLL_NUM = 0;

!+
! If the amount to scroll is too large, don't do any scrolling.
!-

	    IF (ABS (.SCLL_NUM) GEQ .SCR_LNS) THEN SCLL_NUM = 0;

!+
! The sign of SCLL_NUM says which way to scroll, and the magnitude says
! how much.  First position to the bottom or top of the old screen,
! depending on which way we are scrolling.
!-

	    WHILE (.SCLL_NUM NEQ 0) DO

		IF (.SCLL_NUM GTR 0)
		THEN
		    BEGIN
!+
! The cursor is moving down, so scroll the screen up.
!-
		    SCRPTR = .BOT_SCRPTR;
		    REC_NO = .OLD_BOT_RECNO;
		    SCRPTR = .SCRPTR [SCR_NXT_LINE];

		    IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO + 1;

		    OLD_BOT_RECNO = .REC_NO;

		    IF .TI_SCROLL
		    THEN
			BEGIN
			EDT$$SC_POSCSIF (.SCR_LNS - 1, 0);
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);
			END
		    ELSE
			BEGIN
			EDT$$SC_POSCSIF (.MESSAGE_LINE + 1, 0);
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);
			EDT$$SC_POSCSIF (.SCR_LNS - 1, 0);
			END;

		    CS_LNO = .SCR_LNS - 1;
		    EDT$$SC_REPAINT (.SCRPTR, .SCRPTR, 0, 255, 1);
		    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
		    EDT$$SC_RFRELN (.SCRPTR, .TI_SCROLL);
		    TOP_SCRPTR = .TOP_SCRPTR [SCR_NXT_LINE];
		    BOT_SCRPTR = .SCRPTR;
		    SCLL_NUM = .SCLL_NUM - 1;
		    END
		ELSE
		    BEGIN
!+
! The cursor is moving up, so scroll the screen down.
!-
		    SCRPTR = .TOP_SCRPTR;
		    REC_NO = .OLD_TOP_RECNO;

		    IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO - 1;

		    OLD_TOP_RECNO = .REC_NO;
		    SCRPTR = .SCRPTR [SCR_PRV_LINE];
		    EDT$$SC_POSCSIF (0, 0);

		    IF (.TI_TYP EQL TERM_VT52)
		    THEN
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'I'))), 2)
		    ELSE
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'M'))), 2);

		    IF ( NOT .TI_SCROLL)
		    THEN
			BEGIN
			CS_LNO = .SCR_LNS;
			EDT$$SC_ERAALL ();
			END;

		    CS_LNO = 0;
		    EDT$$SC_REPAINT (.SCRPTR, .SCRPTR, 0, 255, 1);
		    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
		    EDT$$SC_RFRELN (.SCRPTR, 1);
		    TOP_SCRPTR = .SCRPTR;
		    BOT_SCRPTR = .BOT_SCRPTR [SCR_PRV_LINE];
		    SCLL_NUM = .SCLL_NUM + 1;
		    END;

	    END;

!+
! Make a final update pass over the screen.  This will be needed if
! no scrolling took place because the new screen is too far from
! the old screen.
!-
	REC_NO = .TOP_RECNO;
	SCRPTR = .TOP_PTR;
	CURSOR_LINE = -1;
	TOP_SCRPTR = .TOP_PTR;
	CS_LNO = 0;

	WHILE ((.CS_LNO LSS .SCR_LNS) AND (.SCRPTR NEQA 0)) DO
	    BEGIN

	    IF ((.SCRPTR [SCR_EDIT_FLAGS] AND (SCR_EDIT_MODIFY OR SCR_EDIT_INSLN OR SCR_EDIT_DELLN)) NEQ 0)
	    THEN
		BEGIN
		ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
		EDT$$SC_RFRELN (.SCRPTR, .ERASE_ALL);
		END;

	    BOT_SCRPTR = .SCRPTR;

	    IF (.SCRPTR EQLA .CUR_SCRPTR) THEN CURSOR_LINE = .CS_LNO;

	    SCRPTR = .SCRPTR [SCR_NXT_LINE];
	    CS_LNO = .CS_LNO + 1;

	    IF (.SCRPTR NEQA 0)
	    THEN
		BEGIN

		IF (.SCRPTR [SCR_LINE_IDX] EQL 0) THEN REC_NO = .REC_NO + 1;

		END;

	    END;

!+
! If there is more room on the screen, erase it if necessary.
!-

	IF (.CS_LNO LSS .BOT_LINE) THEN EDT$$SC_ERAALL ();

	BOT_LINE = .CS_LNO;
!+
! Mark the lines off the screen for repaint in case we have to scroll
! them back on in the next pass thru SC_UPD.
!-

	IF (.FST_SCRPTR NEQA .TOP_SCRPTR)
	THEN
	    BEGIN
	    SCRPTR = .TOP_SCRPTR [SCR_PRV_LINE];
	    EDT$$SC_REPAINT (.FST_SCRPTR, .SCRPTR, 0, 255, 1);
	    END;

	IF (.BOT_SCRPTR NEQA .LST_SCRPTR)
	THEN
	    BEGIN
	    SCRPTR = .BOT_SCRPTR [SCR_NXT_LINE];
	    EDT$$SC_REPAINT (.SCRPTR, .LST_SCRPTR, 0, 255, 1);
	    END;

	END;

!+
! Do the clean-up on the screen data pointers.
!-
    OLD_SEL = .SEL_BUF;
    SCR_REBUILD = 0;
    REC_NO = 0;
    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
    MOVELINE (CS_LN, CUR_SCRLN);
    CSR_SCRPTR = .CUR_SCRPTR;
    CS_OLDCHNO = .CS_CHNO;
    EDT$$SC_POSCSIF (.CURSOR_LINE, .CURSOR_POS);
    CS_LNO = .CURSOR_LINE;
    CUR_COL = .CURSOR_POS;
    EDT$$TI_ENBLAUTREP (1);
    EDT$$OUT_FMTBUF ();
    LN_PTR = CH$PTR (LN_BUF, .CS_CHNO, BYTE_SIZE);
    RECS_INSERTED = 0;
    END;					! of routine EDT$$SC_UPD
%SBTTL 'DELETE_LINE - delete a line on the screen'
ROUTINE DELETE_LINE (				! Delete a line on the screen
    SCRPTR, 					! The line to delete
    REC_NO, 					! It's relative record number
    ERASE_ALL, 					! 1 = screen has been erased
    OLD_TOP_RECNO				! Record number of the top line
    ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Delete one screen line.
!
! FORMAL PARAMETERS:
!
!  SCRPTR		The screen data block to delete
!
!  REC_NO		The relative record number of that line
!
!  ERASE_ALL		1 = the screen has been erased
!
!  OLD_TOP_RECNO	Record number of the top line
!
! IMPLICIT INPUTS:
!
!	FST_SCRPTR
! 	LST_SCRPTR
!	TI_SCROLL
!	TOP_SCRPTR
!	SCR_LNS
!	SCLL_BOT
!	BOT_SCRPTR
!	CS_LNO
!	LST_SCRPTR
!	BOT_LINE
!
! IMPLICIT OUTPUTS:
!
!	TOP_SCRPTR
!	BOT_SCRPTR
!	BOT_LINE
!
! ROUTINE VALUE:
!
!	1 = OK, 0 = must start update over
!
! SIDE EFFECTS:
!
!	Will store into the format buffer
!
!--

    BEGIN

    MAP
	SCRPTR : REF SCREEN_LINE;

    EXTERNAL ROUTINE
	EDT$$SC_ERAALL,				! Erase to end of screen
	EDT$$SC_MOVTOLN,		! Move to a record in the work file relative to the current record
	EDT$$SC_RFRELN : NOVALUE,		! Refresh a screen line
	EDT$$SC_LNDEL,				! Delete a line from data structure
	EDT$$SC_SETSCLLREG,			! Set scrolling region
	EDT$$FMT_LIT,				! Format a literal for output
	EDT$$SC_POSCSIF : NOVALUE,		! Position the cursor
	EDT$$SC_REPAINT : NOVALUE;		! Mark some lines in the screen data base for repaint

    EXTERNAL
	MSGFLG,				! Is a message on the screen
	MESSAGE_LINE,			! Line number for prompts
	TI_TYP,				! Terminal type
	TI_EDIT,				! VT102 editing features
	SCR_LNS,				! Number of lines on screen
	SCLL_BOT,			! Cursor screen line
	FST_SCRPTR : REF SCREEN_LINE,	! First data structure pointer
	BOT_SCRPTR : REF SCREEN_LINE,	! Bottom screen pointer
	LST_SCRPTR : REF SCREEN_LINE,	! Last data structure pointer
	TOP_SCRPTR : REF SCREEN_LINE,	! Top screen line info address
	EOB_SCRPTR : REF SCREEN_LINE,	! EOB screen pointer
	CS_LNO,				! current cursor line
	TI_SCROLL,			! 1 = we have scrolling regions
	BOT_LINE;			! All lines below this one have been erased

    LOCAL
	PRV_SCRPTR : REF SCREEN_LINE,		! Previous screen pointer
	NXT_SCRPTR : REF SCREEN_LINE;		! Next screen pointer

    NXT_SCRPTR = .SCRPTR [SCR_NXT_LINE];
!+
! If we are deleting the top line, make the following line the top line
! unless there are lines preceding it that have been modified or inserted,
! in which case we paint over the deleted line instead of scrolling.
!-

    IF (.SCRPTR EQLA .TOP_SCRPTR)
    THEN
	BEGIN
	PRV_SCRPTR = .SCRPTR [SCR_PRV_LINE];

	IF (.PRV_SCRPTR NEQA 0)
	THEN
!+
! Test for insertion or modification of previous lines.
!-

	    IF ((.PRV_SCRPTR [SCR_EDIT_FLAGS] AND (SCR_EDIT_INSLN OR SCR_EDIT_MODIFY)) NEQ 0)
	    THEN
		BEGIN
!+
! Delete the current line and backup to the previous line for a
! repaint.  The top screen pointer and record number offsets
! must also be updated.  No further processing is needed on this pass.
!-
		EDT$$SC_LNDEL (.SCRPTR);
		TOP_SCRPTR = .PRV_SCRPTR;

		IF ((.PRV_SCRPTR [SCR_LINE_IDX] EQL 0) AND 	!
		    ((.PRV_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0))
		THEN
		    BEGIN
		    .OLD_TOP_RECNO = ..OLD_TOP_RECNO - 1;
		    REC_NO = .REC_NO - 1;
		    END;

		ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
		EDT$$SC_RFRELN (.PRV_SCRPTR, .ERASE_ALL);
		RETURN (0);
		END;

!+
! The previous line is non-existent or has not been modified.  Handle this in the usual way.
!-
	END;

    IF ((.EOB_SCRPTR EQLA .BOT_SCRPTR) AND (.TOP_SCRPTR [SCR_PRV_LINE] NEQA 0))
    THEN
	BEGIN
!+
! The [EOB] appears on the screen, but the buffer is long enough that there is a line
! before the top line that appears on the screen.
! Move the top screen pointer up one line.  This must be done before deleting
! the current line in case the top line is the current line.
!-
	TOP_SCRPTR = .TOP_SCRPTR [SCR_PRV_LINE];
!+
! Adjust the record number of the top line.
!-

	IF ((.TOP_SCRPTR [SCR_LINE_IDX] EQL 0) AND 	!
	    ((.TOP_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0))
	THEN
	    .OLD_TOP_RECNO = ..OLD_TOP_RECNO - 1;

	IF (.TI_SCROLL)
	THEN
	    BEGIN

	    LOCAL
		TMP_SCRPTR : REF SCREEN_LINE,
		SCLL_LINE;

	    SCLL_LINE = .CS_LNO;
	    TMP_SCRPTR = .SCRPTR;
!+
! To speed up deletes, the scrolling line will be the last line which is
! marked for delete.
!-

	    DO
		BEGIN
		SCLL_LINE = .SCLL_LINE + 1;
		TMP_SCRPTR = .TMP_SCRPTR [SCR_NXT_LINE];
		END
	    UNTIL ((.TMP_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0);

!+
! Scroll down
!-
	    EDT$$SC_SETSCLLREG (0, .SCLL_LINE);
	    EDT$$SC_POSCSIF (0, 0);
	    EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'M'))), 2);
	    EDT$$SC_LNDEL (.SCRPTR);
	    END
	ELSE
!+
! Repaint from the first line to the current line on a noscroll terminal.
!-
	    BEGIN

	    LOCAL
		SAV_CS_LN;

	    EDT$$SC_LNDEL (.SCRPTR);

	    IF (.NXT_SCRPTR NEQA 0) THEN EDT$$SC_REPAINT (.NXT_SCRPTR, .LST_SCRPTR, 0, 255, 0);

	    SAV_CS_LN = .CS_LNO;
	    EDT$$SC_POSCSIF (0, 0);
!+
! Scroll down.
!-

	    IF (.TI_TYP EQL TERM_VT52)
	    THEN
		EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'I'))), 2)
	    ELSE
		EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'M'))), 2);

!+
! If we've done a scroll then the message is no longer on the screen.
!-
	    MSGFLG = 0;
	    BOT_LINE = .BOT_LINE + 1;
	    CS_LNO = .SCR_LNS;
	    EDT$$SC_ERAALL ();
	    CS_LNO = .SAV_CS_LN;
	    END;

	END
    ELSE
	BEGIN
!+
! Either [EOB] does not appear on the screen or, if it does, the buffer is short enough
! that it all fits on the screen.  We will be scrolling up.
! If we are deleting the top line, make the next line the top line.  We don't need to
! worry about the top line record number since deleted lines have the record number
! of the next following non-deleted line.
!-
	PRV_SCRPTR = .TOP_SCRPTR;

	IF (.SCRPTR EQLA .TOP_SCRPTR) THEN TOP_SCRPTR = .NXT_SCRPTR;

	IF ((.TI_SCROLL) AND (.CS_LNO LSS (.SCR_LNS - 1)))
	THEN
	    BEGIN
!+
! Set the scrolling region so we can update the screen without repainting text
! that has moved up.
!-

	    IF (.TI_EDIT)
	    THEN
!+
! Use VT102 edit feature
!-
		BEGIN
		EDT$$SC_POSCSIF (.CS_LNO, 0);
		EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), '[M'))), 3);
		END
	    ELSE
		BEGIN
!+
! Simulate edit feature.
!-
		EDT$$SC_SETSCLLREG (.CS_LNO, .SCR_LNS);
		EDT$$SC_POSCSIF (.SCR_LNS - 1, 0);
		EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);
		END;

!+
! Free the deleted line.
!-
	    EDT$$SC_LNDEL (.SCRPTR);
	    END
	ELSE
	    BEGIN
!+
! If we cannot use the scrolling region, repaint the screen from the point
! of the deletion to the bottom.  If we're deleting the top line, then
! just scroll up instead of repainting.
!-

	    IF (.SCRPTR EQLA .PRV_SCRPTR)
	    THEN
		BEGIN
		EDT$$SC_LNDEL (.SCRPTR);
		EDT$$SC_POSCSIF (.MESSAGE_LINE + 1, 0);
		EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);
		END
	    ELSE
		BEGIN
		EDT$$SC_LNDEL (.SCRPTR);

		IF (.NXT_SCRPTR NEQA 0)
		THEN

		    IF (.NXT_SCRPTR EQLA .EOB_SCRPTR) OR ((.NXT_SCRPTR [SCR_EDIT_FLAGS] AND
			SCR_EDIT_DELLN) EQL 0)
		    THEN
			EDT$$SC_REPAINT (.NXT_SCRPTR, .LST_SCRPTR, 0, 255, 0);

		END;

	    END;

!+
! Adjust the bottom screen pointer if it is not the EOB.
!-

	IF ((.BOT_SCRPTR NEQA 0) AND (.BOT_SCRPTR NEQA .EOB_SCRPTR))
	THEN
	    BOT_SCRPTR = .BOT_SCRPTR [SCR_NXT_LINE];

	END;

!+
! Make another pass over the screen data.
!-
    RETURN (0);
    END;					! of routine DELETE_LINE
%SBTTL 'INSERT_LINE - insert a line on the screen'
ROUTINE INSERT_LINE (				! Insert a line on the screen
    SCRPTR, 					! The line to insert
    REC_NO, 					! It's relative record number
    ERASE_ALL, 					! 1 = screen has been erased
    OLD_TOP_RECNO				! Record number of the top line
    ) =

!++
! FUNCTIONAL DESCRIPTION:
!
!	Insert one screen line.  It may be marked inserted or deleted.
!	This routine is not called unless it has some kind of edit.
!
! FORMAL PARAMETERS:
!
!  SCRPTR		The screen data block to insert
!
!  REC_NO		The relative record number of that line
!
!  ERASE_ALL		1 = the screen has been erased
!
!  OLD_TOP_RECNO	Record number of the top line
!
! IMPLICIT INPUTS:
!
!	TI_SCROLL
!	TOP_SCRPTR
!	SCR_LNS
!	SCLL_BOT
!	BOT_SCRPTR
!	CS_LNO
!	LST_SCRPTR
!	BOT_LINE
!
! IMPLICIT OUTPUTS:
!
!	TOP_SCRPTR
!	BOT_SCRPTR
!	BOT_LINE
!
! ROUTINE VALUE:
!
!	1 = OK, 0 = must start update over
!
! SIDE EFFECTS:
!
!	Will store into the format buffer
!
!--

    BEGIN

    MAP
	SCRPTR : REF SCREEN_LINE;

    EXTERNAL ROUTINE
	EDT$$SC_LNDEL,				! Free a deleted line
	EDT$$SC_SETSCLLREG,			! Set scrolling region
	EDT$$FMT_LIT,				! Format a literal for output
	EDT$$SC_POSCSIF : NOVALUE,		! Position the cursor
	EDT$$SC_MOVTOLN,		! Move to a record in the work file relative to the current record
	EDT$$SC_RFRELN : NOVALUE,		! Refresh a screen line
	EDT$$SC_REPAINT : NOVALUE;		! Mark some lines in the screen data base for repaint

    EXTERNAL
	MESSAGE_LINE,			! Line number for error msgs
	TI_EDIT,				! VT102 editing features
	SCR_LNS,				! Number of lines on screen
	SCLL_BOT,			! Cursor screen line
	BOT_SCRPTR : REF SCREEN_LINE,	! Bottom screen pointer
	LST_SCRPTR : REF SCREEN_LINE,	! Last data structure pointer
	TOP_SCRPTR : REF SCREEN_LINE,	! Top screen line info address
	EOB_SCRPTR : REF SCREEN_LINE,	! EOB screen pointer
	CS_LNO,				! current cursor line
	TI_SCROLL,			! 1 = we have scrolling regions
	BOT_LINE;			! All lines below this one have been erased

    LOCAL
	NXT_SCRPTR : REF SCREEN_LINE;		! Next screen pointer

!+
! Now check for inserted lines and perform scrolls based upon this information
!-

    IF ((.CS_LNO GEQ .SCLL_BOT) AND (.BOT_LINE GEQ .SCR_LNS))
    THEN
	BEGIN
	NXT_SCRPTR = .SCRPTR [SCR_NXT_LINE];

	IF (.TI_SCROLL)
	THEN
	    BEGIN

	    IF (.NXT_SCRPTR NEQA 0)
	    THEN

		IF ((.NXT_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0)
		THEN
		    EDT$$SC_LNDEL (.NXT_SCRPTR)
		ELSE
		    BEGIN
!+
! Scroll up.
!-
		    CS_LNO = .CS_LNO - 1;
		    EDT$$SC_SETSCLLREG (0, .CS_LNO + 1);
		    EDT$$SC_POSCSIF (.CS_LNO, 0);
		    EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);	! Scroll up
!+
! Mark the top line for repaint since it is moving off the screen.
!-
		    EDT$$SC_REPAINT (.TOP_SCRPTR, .TOP_SCRPTR, 0, 255, -1);
		    TOP_SCRPTR = .TOP_SCRPTR [SCR_NXT_LINE];
!+
! Adjust the record number of the top line.
!-

		    IF ((.TOP_SCRPTR [SCR_LINE_IDX] EQL 0) AND 	!
			((.TOP_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0))
		    THEN
			.OLD_TOP_RECNO = ..OLD_TOP_RECNO + 1;

		    END;

	    END
	ELSE
	    BEGIN
!+
! Do a repaint from the top down and scroll up once if we have a noscroll terminal.
!-
	    EDT$$SC_REPAINT (.SCRPTR, .LST_SCRPTR, 0, 255, 1);
	    EDT$$SC_POSCSIF (.MESSAGE_LINE + 1, 0);
	    EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_LF)))), 1);
	    TOP_SCRPTR = .TOP_SCRPTR [SCR_NXT_LINE];
!+
! Adjust the record number of the top line.
!-

	    IF ((.TOP_SCRPTR [SCR_LINE_IDX] EQL 0) AND 	!
		((.TOP_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) EQL 0))
	    THEN
		.OLD_TOP_RECNO = ..OLD_TOP_RECNO + 1;

	    RETURN (0);
	    END;

	END
    ELSE
	BEGIN

	IF (.TI_SCROLL)
	THEN
	    BEGIN
	    NXT_SCRPTR = .SCRPTR [SCR_NXT_LINE];

	    IF (.NXT_SCRPTR NEQA 0)
	    THEN

		IF ((.NXT_SCRPTR [SCR_EDIT_FLAGS] AND SCR_EDIT_DELLN) NEQ 0)
		THEN
		    EDT$$SC_LNDEL (.NXT_SCRPTR)
		ELSE
		    BEGIN
!+
! Scroll down.
!-

		    IF (.TI_EDIT)
		    THEN
!+
! Use VT102 edit feature
!-
			BEGIN
			EDT$$SC_POSCSIF (.CS_LNO, 0);
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), '[L'))), 3);
			END
		    ELSE
			BEGIN
!+
! Simulate edit feature
!-
			EDT$$SC_SETSCLLREG (.CS_LNO, .SCR_LNS);
			EDT$$SC_POSCSIF (.CS_LNO, 0);
			EDT$$FMT_LIT (CH$PTR (UPLIT (%STRING (%CHAR (ASC_K_ESC), 'M'))), 2);	! Scroll down
			END;

!+
! If the bottom line will move off the screen, arrange to repaint it if it should move back on.
!-

		    IF ((.BOT_SCRPTR NEQA 0) AND (.BOT_LINE GEQ (.SCR_LNS - 1)))
		    THEN
			BEGIN
			EDT$$SC_REPAINT (.BOT_SCRPTR, .BOT_SCRPTR, 0, 255, 0);
			BOT_SCRPTR = .BOT_SCRPTR [SCR_PRV_LINE];
			END;

!+
! The bottom line may be lower on the screen.  It doesn't matter much if BOT_LINE is too large.
!-
		    BOT_LINE = .BOT_LINE + 1;
		    END;

	    END
	ELSE
	    BEGIN
	    EDT$$SC_REPAINT (.SCRPTR, .LST_SCRPTR, 0, 255, 1);
!+
! If the bottom line will move off the screen, arrange to repaint it if it should move back on.
!-

	    IF ((.BOT_SCRPTR NEQA 0) AND (.BOT_LINE GEQ (.SCR_LNS - 1)))
	    THEN
		BEGIN
		EDT$$SC_REPAINT (.BOT_SCRPTR, .BOT_SCRPTR, 0, 255, 0);
		BOT_SCRPTR = .BOT_SCRPTR [SCR_PRV_LINE];
		END;

!+
! The bottom line may be lower on the screen.  It doesn't matter much if BOT_LINE is too large.
!-
	    BOT_LINE = .BOT_LINE + 1;
	    RETURN (0);
	    END;

	END;

    ASSERT (12, EDT$$SC_MOVTOLN (.REC_NO));
    EDT$$SC_RFRELN (.SCRPTR, .ERASE_ALL);
    RETURN (1);
    END;					! of routine INSERT_LINE
!<BLF/PAGE>
END						! of module EDT$SCRUPDATE

ELUDOM