; MODULE: ZCPR3 Full Screen Editor ; AUTHOR: Rob Friefeld ; DATE: 14 Nov 1990 if 0 Input: HL = location in buffer to start editing Return: Z = abort endif ;================================================================== ; ; D E F I N I T I O N S S E C T I O N ; ;================================================================== public edit ; Calling program determines these ext txtlns ; Contains number of lines for text ext bufsz ; DW Size of editing buffer ext loffset ; Contains # unused lines at top of screen ext statline ; Routine puts cursor on a status line ext rtmarg ; Contains right margin ext insflg ; Contains insert/overwrite flag ; System library routines ext cin,cout7,crlf,caps,print,padc ext gotoxy,ereol,dellin,inslin,clreos,curon,curoff,getcrt ; Standard definitions include sysdef.lib ; Local definitions lbufwid equ 255 ; Line buffer size hscr equ 30 ; Horizontal scroll tabsz equ 4 ; Tab must be 2,4,8,... oflchr equ '+' ; Line over flow ; Macro definitions pushm macro push hl push de push bc endm popm macro pop bc pop de pop hl endm ;========================================================== ; Control key bindings for NTS ; - The length of the list must not be changed. ; - The order of the list must not be changed. ; Normal commands are control chars ^A .. ^^ and 1fh for DEL ; There are four meta-keys which access commands keyed to them. ; - Meta-key #1 ^A ... + 80h + 0 ; - Meta-key #2 ^A ... + 80h + 20h ; - Meta-key #3 ^A ... + 80h + 40h ; - Meta-key #4 ^A ... + 80h + 60h ; Disabled keys use '-'. ; Generate control key from char and shift factor key macro x,m db x-'@'+m endm ; Shift factors for meta-keys k0 equ 0 k1 equ 80h k2 equ 80h + 20h k3 equ 80h + 40h k4 equ 80h + 60h cmd_list: ; Meta keys ; key 'K',k0 ; Meta #1 key 'Q',k0 ; Meta #2 key 'O',k0 ; Meta #3 db '-' ; Meta #4 ; Editing ; key 'H',k0 ; Backspace key 'S',k0 ; Char left key 'D',k0 ; Char right key 'E',k0 ; Line up key 'X',k0 ; Line down key 'F',k0 ; Word right key 'A',k0 ; Word left key 'J',k0 ; Line end/ line start key 'S',k2 ; Line start key 'D',k2 ; Line end key 'R',k0 ; Up screen key 'C',k0 ; Down screen key 'R',k2 ; First screen key 'C',k2 ; Last screen key 'G',k0 ; Delete char db 1fh ; Delete left key 'T',k0 ; Delete word right key 'Y',k0 ; Delete line key 'Y',k2 ; Delete to end of line key 'M',k0 ; Carriage return key 'N',k0 ; Insert carriage return key 'I',k0 ; TAB key 'V',k0 ; Toggle insert/overwrite key 'Z',k2 ; Zap to end key 'X',k1 ; Save & exit key 'Q',k1 ; Quit key 'U',k0 ; Undo changes to line key 'B',k0 ; Reformat key 'R',k3 ; Set right margin cmdlen equ $ - cmd_list cmd_vector: dw meta_key1 ;^k dw meta_key2 ;^q dw meta_key3 ;^o dw meta_key4 ;? dw delft ;^h dw bsp ;^s dw fsp ;^d dw pvline ;^e dw nxline ;^x dw fwrd ;^f dw bwrd ;^a dw linend ;^j dw linbeg ;^qs dw linend1 ;^qd dw upscr ;^r dw dnscr ;^c dw topscr ;^qr dw endscr ;^qc dw delete ;^g dw delft ;del dw delwrd ;^t dw dline ;^y dw deleol ;^qy dw cartn ;cr dw cartn3 ;^n dw entertab ;tab dw instog ;^v dw zap ;^qz dw sav$ex ; ^kx Save edit, exit dw nosav$ex ; ^kq Quit, no save dw undo ;^u dw reform ;^b dw setright ;^or veclen equ $ - cmd_vector if veclen ne cmdlen*2 *** COMMAND TABLE ERROR endif ;================================================================== ; ; M A I N C O D E S E C T I O N ; ;================================================================== ; ----------------- if 0 CONSTANTS: crtwid = 80 (can be more) width = crtwid-2 is useable line width (78) txtlns = lines used for text loffset = free lines at top of screen VARIABLES: linptr - pointer to start of current line nline - current line (0..txtlns-1) BUFFER STRUCTURE: allow at least crtwid bytes for each line plus a line of overflow LINE BUFFER: Line being edited is moved to the line buffer. |5|H|E|L|L|O|0|...|0| / \ \ (lcount): line: terminating 0's endif ; ----------------- EDIT: ld (estksav),sp ld sp,estack ld (eindex),hl ; Store passed start location ld de,(BUFSZ) ; Calculate and save buffer top add hl,de ld (buftop),hl call GETCRT ld a,(hl) ; CRTWID sub 2 ld (width),a ; Avoid wrap for all terminals ld a,(TXTLNS) ; Number of lines to use ld (n$txtlns),a ; Save it call topline ; Initialize pointers to first line call online ; Edit current line ;================================================================== ; ; E D I T C O M M A N D L O O P ; ;================================================================== ; The command loop address is pushed onto the stack so that the last ; subroutine used will return here. A key is input. If text, it is ; entered. If control, it is matched to the (external) list of command ; keys to obtain an offset into the control vector table, followed by ; a jump to that address. ecmd: call CURON call CIN ; Get next char push af call CUROFF pop af exx ; Main regs must be preserved ld hl,ecmd ; Save address so a return comes back here push hl ld hl,meta_flag ; Get meta flag or (hl) ; Mask in possible previous shift key exx ; Restore main regs cp 20h ; Control key? jr c,control_key ; Yes cp 7fh ; High bit set? jp c,enter ; No, must be text control_key: exx ; Preserve main regs call menuinp ; Convert key ld hl,cmd_vector push hl ld hl,CMD_LIST ; Scan command list ld bc,CMDLEN cpir pop hl jr nz,no_match ld a,CMDLEN-1 ; Point to address in vector table sub c add a,a ld c,a add hl,bc ld c,(hl) inc hl ld b,(hl) push bc ; Address to jump to no_match: exx ; Restore regs! ret ; Convert a key entry to control char tagged for shift key ; Now in alt regs with hl = meta_flag menuinp: and 1fh ; Convert to control or (hl) ; Mask in shift ld (hl),0 ; Reset flag ret ; Mark meta-key flag meta_key1: ld a,10000000b jr meta_key meta_key2: ld a,10100000b jr meta_key meta_key3: ld a,11000000b jr meta_key meta_key4: ld a,11100000b meta_key: ld (meta_flag),a ret meta_flag: db 0 ; ============================================================== ; ON LINE ROUTINES, EDITING CURRENT LINE IN LINE BUFFER ; ; The current line is copied into the line buffer and edited with these ; routines. On leaving the line, it is placed back into the body of the ; text. UNDO reloads the line buffer from the main text. ; WHILE ON LINE: ; B = CHAR COUNT (0..width) C = CURSOR POSITION (0..char count) ; HL = MEM POSITION D = SCROLL POSITION E = SCROLL + WIDTH ; Backspace ; bsp: xor a cp c ; Cursor position jr nz,bsp1 bspp: call pvline1 ; Backspace to previous line jp linend1 ; Position at end ; Return Z = backspace not done, NZ = all OK bsp1: xor a ; cp b ; ret z ; 0 length line cp c ret z ; At start call bchar or -1 ret ; Forward Space ; fsp: call fchar ; Forward a char fsp1: jp z,nxline ; At eoln, next line ret ; Forward Word ; fwrd: call fwrd1 jr fsp1 fwrd1: ld a,(hl) or a ret z ; At EOLN fwrd2: call wrdsep ; Are we on a word separator? jr z,fwrd3 ; Yes call fchar ; No, advance until we find one jr fwrd2 fwrd3: call fchar ; Word sep found, advance 1 more space ld a,(hl) ; Are we on a blank? cp ' ' jr z,fwrd3 ; Don't quit on a blank ret ; Back Word ; bwrd: call bwrd1 jp z,bspp ret bwrd1: ld a,c or a ret z ; At line beginning, go to prev line bwrd2: call bsp1 jr z,bwrd3 ; No where to go ld a,(hl) cp ' ' jr z,bwrd2 ; Backspace over blanks call pwrdsep ; Now backspace until next wordsep jr nz,bwrd2 bwrd3: or -1 ret ; Is previous char a word separator? pwrdsep: dec hl call wrdsep inc hl ret ; Define Word Separators ; wrdsep: ld a,(hl) or a ret z ;EOLN cp tab ret z cp ' ' ret z cp ',' ret z cp ';' ret z cp '.' ret z cp ':' ret ; Delete Char ; delete: ld a,(hl) ; EOLN? or a jp z,lnappend ; Concat next line dele: call delmem ; In memory jp ptail ; Print line tail delmem: ld (hl),0 ; Terminal 0 or char to be deleted ld a,b sub c ; A = (count-position) = chars from end ret z ; At eoln, no char dec b ret z ; Single char line dec a ret z ; On last char, just deleted it delmem1: inc a ; To move terminal 0 in pushm ld d,h ; Dest is current pos ld e,l inc hl ; Source, terminal 0 ld c,a ; Count, line tail ld b,0 ldir ; Block move popm ret ; Delete Char Left ; delft: xor a cp c jp z,dlinelft ; At beginning of line call bsp1 jr dele ; Delete Word Right ; delwrd: ld a,(hl) or a jr z,delete delwrd0: call wrdsep jr z,delwrd2 ld a,b cp c jr z,dele ; Exit delwrd1: call delmem jr delwrd0 delwrd2: call delmem ; Don't quit on a blank ld a,(hl) cp ' ' jr z,delwrd2 jp ptail ; Delete to EOLN ; deleol: call EREOL ld b,c ld a,c ld (lcount),a jp zline ; Insert/Overwrite Toggle ; instog: ld a,(insflg) ; Flag 0 -> owrt cpl ld (insflg),a ret ; TAB ; entertab: ld a,tab jr enter ; At margin, wrap line ; New char on stack linewrap: call pwrdsep call nz,bwrd1 ; Back up to start of word call cartn3 ; Break line call linend xor a cp c ; At start of line? jr nz,linew1 ; No pop af cp ' ' ; Don't start new line with SP ret z push af linew1: pop af ; Enter a Char ; enter: push af call getpos ; Where the devil are we ld a,(RTMARG) cp e jr z,linewrap ; At margin, wrap line pop af ex af,af' ; Save char ld a,b ; At eoln? sub c jr z,ovrwrt ; Yes, no need for insert mode ld a,(insflg) ; Which mode are we in? or a ; 0 = overwrite, nz = insert jr nz,insert ; Enter Char in Overwrite Mode ; ovrwrt: ld a,b cp lbufwid-2 ; Line full? jr c,ovr1 ; No sub c ; At EOLN? jp z,beep ovr1: ex af,af' ; Recover char cp tab jr nz,owrt ovr2: ld a,(hl) or a jr z,ovr3 call fchar call getpos and tabsz-1 jr nz,ovr2 ret ovr3: ld a,tab owrt: ld e,a ; Save char for a minute ld a,(hl) ; What are we replacing? cp tab ld a,e ld (hl),a ; Put char in place call z,ptail ; A tab overwrote some text owrt1: call fchar ld a,b ; Char count -> a cp c ret nc ; No need to incr char count inc b ; We are inside of line ret ; Enter Char in Insert Mode ; insert: ld a,b ; Line full? cp lbufwid-2 jp nc,beep insrt: ld a,b ; At eoln? sub c ; A = # chars to eoln jr z,ovr1 ; Yes, really want overwrite call insmem ; Push chars down to make room ex af,af' ; Recover char ld (hl),a ; Place char in line call ptail ; Reprint line from here inc b jp fchar ; Advance cursor insmem: push bc ; Make room for char in line push de ld c,a ; Bc = # chars to move ld b,0 add hl,bc ; Dest is new eoln ld d,h ; Now in DE ld e,l dec hl ; Source is current eoln lddr ; Tail move pop de pop bc ; Recover char count, crs pos info inc hl ; Hl to next char ret ; Line End/Start Toggle ; linend: ; Go to eoln or, if there, to start of line ld a,b cp c jr z,linbeg linend1: ld hl,line ; Eoln routine ld c,b ; Char position at end ld e,b ld d,0 add hl,de ; HL at EOLN call comppos ; Position from start of line jp c,movcrs ; On first screen ld a,(width) sub b neg ld d,a call hscroll jp movcrs ; Cursor to eoln comppos: call getpos ld a,(width) cp e ccf ret linbeg: xor a ; Start of line routine ld hl,line ld c,a cp d jp z,pcr ; On first screen ld d,a call pcr jp ptail ; Compute cursor position from start of scroll ; Return value in a and e getpos: xor a ld e,a or c ret z ; At start pushm ld hl,line ld e,d ld d,0 add hl,de ; Start of scroll ld a,c ; Char pos sub e ; Scroll pos jr z,getpos3 ; Start of screen ld e,d ; 0 to E ld b,a ; NZ loop counter ld c,tabsz-1 ld d,tab getpos1: ld a,d cp (hl) inc hl jr nz,getpos2 getpos1a: inc e ld a,c and e jr nz,getpos1a dec e getpos2: inc e djnz getpos1 ld a,e getpos3: popm ld e,a ret ; Move forward one character ; This is complex because of horizontal scroll and tabbing. ; fchar: ld a,(hl) or a ret z push af call comppos call nc,hscroll pop af inc hl inc c cp tab jp nz,COUT7 call comppos jp c,movcrs hscroll: ld a,(width) add d hscr1a: sub hscr ld d,a hscr1b: push hl push bc ld c,d ld b,0 ld hl,line add hl,bc call pcr call ptail pop bc pop hl call movcrs or -1 ret ; Move back one character ; bchar: call getpos call z,bchar1 dec hl dec c ld a,bs call COUT7 ld a,(hl) cp tab ret nz jp movcrs bchar1: ld a,d cp hscr jr nc,hscr1a ld d,0 jr hscr1b ; ; LINE MANIPULATION ROUTINES, EDITOR MOVES BETWEEN LINES ; newscr: call prteos ; Refresh screen from current line ; FIRST TIME ON NEW LINE. INITIALIZE HL,BC TO EDIT MODE, CURSOR AT START online: call getline ; Load the line into edit buffer call zline ; Zero the tail ld hl,lcount ld b,(hl) ; Current char count inc hl ; First char xor a ld c,a ; Start of line pos ld d,a ; Scroll pos jp movcrs ; LEAVING A LINE. SAVE COUNT, ZERO OUT TAIL offline: ld hl,lcount ld (hl),b call zline call pcr xor a or d inc hl call nz,prtlin0 dec hl jp putline ; Restuff line ; UNDO EDIT OF CURRENT LINE undo: call online call ptail jp pcr ; GO TO NEXT LINE. RETURN HL -> START, NZ=OK,Z=NO MORE nxline: call getpos ld (crsave),a call nxline1 nxlinex: ld a,(hl) ; At EOLN? or a ret z ; Yes ld a,(crsave) ; Want SOLN? or a ret z ; Yes nxlinex1: call fchar ; Advance a char ret z ; EOLN call getpos ; Where are we now? ld a,(crsave) cp e ; Compare old pos to current ret z ; Exactly there jr nc,nxlinex1 ; Not there yet ret ; Past it (due to TAB) nxline1: call offline call incline jr nz,online nxline2: dec hl ; End of screen ld a,(hl) cp lf inc hl jr nz,online ld a,(hl) cp eof jr z,online jp addline ; GO TO PREVIOUS LINE pvline: call getpos ; Keep current cursor pos ld (crsave),a call pvline1 jr nxlinex pvline1: call offline pvline1a: call decline jr nz,pvlinex pvline2: call prvline ld (linptr),hl jr z,pvlinex ld a,(LOFFSET) or a jr nz,pvline3 call INSLIN call prtlin0 jr pvlinex pvline3: call prteos pvlinex: jp online ; CARRIAGE RETURN. GO TO NEXT LINE cartn: ld a,(insflg) or a jr nz,cartn1 ; Insert mode push hl ld hl,(linptr) ld a,(hl) pop hl cp eof jp nz,nxline ; Not at eof cartn1: call cartn2 ; Make a hole in line for crlf call cartn2 call clfill call offline call newscr jp nxline cartn2: inc b ld a,b sub c jp insmem cartn3: ld a,c or a jr nz,cartn1 ; Inside line, insert cr ; INSERT A BLANK LINE iline: call offline ld bc,(linptr) ; Move source push bc pop de inc de inc de ; Move dest = source + cr,lf call endmove ; Make room ld hl,(linptr) call clfill ; Put in cr,lf ld a,(LOFFSET) or a push af call z,INSLIN pop af call nz,prteos jp online ; ...and go ; DELETE A LINE dline: call offline ; Save char count ld hl,(linptr) push hl call nxtline push hl pop bc ; Start of next line pop de ; Dest call endmove call DELLIN jp newscr ; Update screen ; APPEND NEXT LINE ; lnappend: call nxline1 ; APPEND LINE TO PREVIOUS dlinelft: call offline ld a,(lcount) push af call decline ; Make sure there is room for this call getline ; To get line count in B call incline ; Back to where we were, no effect on B pop af add b jr c,dlft1 ; Overflow cp lbufwid jr nc,dlft1 ; Overflow push bc ; Save line count of prev line ld bc,(linptr) ; Delete preceding crlf push bc pop de dec de dec de call endmove call pvline1a ; Get to start of previous line call newscr pop bc ; Recover old line count ld c,b xor a cp b jr z,dlft1 inc hl djnz $-1 ld b,c ld a,(lcount) ld b,a jp movcrs dlft1: call online ret ; CLEAR FROM CURSOR TO EOF zap: ld (hl),eof ld b,c inc b call offline call newscr jp linend ; ADD A LINE AT BOTTOM OF SCREEN ; Currently ON last line addline: call nxtline ld (linptr),hl xor a call crslin call DELLIN ld a,(TXTLNS) dec a call crslin call prtlin0 jp online ; TOP SCREEN topscr: call offline xor a call crslin call topline ; Set pointers jp newscr ; UP ONE SCREEN upscr: call offline call decline jr z,upscr2 call decline jr nz,$-3 jp online upscr2: ld a,(TXTLNS) dec a ld b,a ld hl,(linptr) upscr2a: call prvline jr z,upscr2b djnz upscr2a upscr2b: ld (linptr),hl jp newscr ; DOWN SCREEN dnscr: call offline call incline jr z,dnscr2 dnscr1a: call incline jr nz,dnscr1a jp online dnscr2: cp eof jr z,endscr0 dnscr2b: xor a call crslin ld (nline),a ld hl,(linptr) call prteos ld hl,(linptr) dnscr2c: call incline ; Find EOF jp z,online call CRLF jr dnscr2c ; END SCREEN endscr: call offline endscr0: call endset ; Find end ld a,(TXTLNS) srl a ld b,a ; txtlns/2 call prvline djnz $-3 ld (linptr),hl xor a call crslin ld (nline),a call prteos endscr1: call incline ; Find EOF jr z,endscr2 call CRLF jr endscr1 endscr2: call online jp linend ; ; LINE AND BUFFER UTILITY ROUTINES ; ; SET UP ON FIRST LINE TO BE EDITED - LINPTR, NLINE topline: ld hl,(eindex) ld (linptr),hl xor a ld (nline),a ret ; GO TO NEXT LINE. RETURN HL -> NEXT LINE, NZ=OK. AFFECT ONLY HL,AF REGS ; LOAD LINPTR AND NLINE WITH NEW VALUES incline: push bc push de ld hl,(linptr) ld a,(hl) cp eof jr z,incl0 ld bc,(n$txtlns) ld a,c dec a cp b jr z,incl0 ; At max inc b ld (n$txtlns),bc call nxtline jp z,incl1 ; EOF encountered before EOLN ld (linptr),hl or -1 incl0: pop de pop bc ret incl1: dec b ld (n$txtlns),bc xor a jr incl0 ; GO TO PREVIOUS LINE RETURN HL -> NEXT LINE, NZ=OK. AFFECT ONLY HL,AF. ; LOAD LINPTR AND NLINE decline: push bc push de ld hl,(linptr) ld a,(nline) ; Line number or a jr z,decl0 ; At min dec a ld (nline),a call prvline ld (linptr),hl or -1 decl0: pop de pop bc ret ; ZERO LINE TAIL ; CHANGE ONLY AF zline: push hl push bc ld hl,lcount ld c,(hl) ; Char count ld b,0 add hl,bc inc hl ; Hl->eoln ld a,lbufwid sub c dec a jr z,zline0 ld b,a ; # of 0's ld (hl),0 inc hl djnz $-3 zline0: pop bc pop hl ret ; GET A LINE OF TEXT TO LINE BUFFER ; Enter with linptr-> start of line getline: ld hl,(linptr) ; Source ld de,line ; Dest ld bc,00FFh ; B accumulates char count getl1: ld a,(hl) cp cr jr z,getl2 cp eof jr z,getl2 ldi inc b jr getl1 getl2: ld a,b ld (lcount),a ; Char count xor a ld (de),a ; Terminating 0 ret ; PUT LINE BUFFER INTO TEXT putline: ld hl,(linptr) ; Start of current line push hl ld bc,(lcount) inc c ; Inc count for cr,lf inc c ld b,0 add hl,bc ex de,hl ; DE - destination pop hl call nxtline push hl pop bc ; BC - source call endmove ret c ; Error ld hl,line ; Now move line buf into hole ld de,(linptr) putl1: ld a,(hl) or a jr z,putl2 ldi jr putl1 putl2: ex de,hl ld a,(hl) cp eof call nz,clfill ld hl,(buftop) ; Guarantee an EOF by top of buffer ld (hl),eof xor a ret clfill: ld (hl),cr inc hl ld (hl),lf inc hl ret endmove: call endset ; MOVE MEMORY BLOCK ; Input: BC - start, HL - end, DE - dest ; Output: Block moved. Return NC = OK, C = error movm: ; Compute block length xor a sbc hl,bc ; end-start ret c ; Error - end before start push hl ; Swap HL,BC push bc pop hl ; HL = start pop bc ; BC = block size ; Head move or tail move? push hl xor a sbc hl,de ; Start - dest pop hl ret z ; Null move jr c,movm1 ; Tail move ; Head move inc bc ; BC = # bytes to move ldir xor a ret ; Tail move movm1: add hl,bc ; Add length to start ex de,hl add hl,bc ; Add length to dest ex de,hl inc bc ; # bytes lddr ; Tail move xor a ret ; SEARCH FOR NEXT LINE OF TEXT ; HL -> starting point ; Return, HL -> next line, Z on EOF nxtline: ld a,(hl) ; Look at char cp eof ret z inc hl ; Bump pointer cp lf jr nz,nxtline or -1 ret ; SEARCH FOR START OF PREVIOUS LINE OF TEXT ; Return HL -> start of line ; Z - At top of buffer, NZ - OK prvline: push bc ld de,(eindex) ; Are we already at beginning of file? push hl xor a sbc hl,de pop hl jr z,prv0 ; Yes, quit now. dec hl ; This should hold a lf. If not, fine. prvlp: dec hl xor a push hl sbc hl,de pop hl jr c,prvx ; Yes, so we are done ld a,(hl) ; Look for last lf cp lf jr nz,prvlp ; Haven't found lf yet prvx: or -1 inc hl prv0: pop bc ret ; PRINT LINES FROM CURRENT LINE NUMBER TO END prteos: ld bc,(n$txtlns) ; B = nline (0..txtlns-1), C = txtlns ld a,c sub b ; Lines to end (1..txtlns) ld b,a ld hl,(linptr) call prteos1 ld c,0 call movcrs ret prteos1a: call CRLF call nxtline prteos1: push hl call cr$clr call prtlin0 pop hl djnz prteos1a jp pcr ; Print to end of line prtlin0: xor a ld c,a prtlin: push hl push de ld d,a ld a,(width) ld e,a prtlin1: ld a,(hl) or a jr z,prtlinx cp eof jr z,prtlinx1 cp cr jr z,prtlinx cp tab jr z,prtlin2 call COUT7 inc hl inc d ld a,e cp d jr nc,prtlin1 prtlin1a: call PRINT dc oflchr,bs prtlinx: or -1 prtlinx1: pop de pop hl ret prtlin2: ld a,' ' call COUT7 inc d ld a,d cp e jr nc,prtlin1a and tabsz-1 jr nz,prtlin2 inc hl jr prtlin1 ; Print Line Tail ptail: push hl call EREOL call getpos call prtlin pop hl jp movcrs ; Return cursor ; Get address of EOF in HL endset: push bc ld hl,(eindex) ld a,eof ld bc,(BUFSZ) cpir dec hl pop bc ret ; MISC ROUTINES ; cr$clr: call pcr jp EREOL pcr: ld a,cr jp COUT7 beep: ld a,bell jp COUT7 ; Move cursor only from current line to line A = n crslin: push af push hl ld hl,LOFFSET add a,(hl) ld h,a inc h ld l,1 call GOTOXY pop hl pop af ret ; MOVE CURSOR TO COLUMN IN D movcrs: push af push hl call getpos ld hl,(n$txtlns) ; H gets line # ld l,a ; Position (0...) inc l ; Col (1...) inc h ; Convert to row # ld a,(LOFFSET) add h ld h,a call GOTOXY pop hl pop af ret ; ; EXITS ; sav$ex: or -1 jr edexit nosav$ex: xor a edexit: push af call offline ; Update buffer ld a,(TXTLNS) ld b,a ld a,(nline) ; Space to end of text sub b ld b,a edexit0: call CRLF inc b jr nz,edexit0 call CURON pop af ld sp,(estksav) ret ; ; SPECIAL ROUTINES ; ; Save edit environment savpos: ld (hlsave),hl ld (desave),de ld (bcsave),bc ret ; Restore edit environment, including cursor rstpos: ld hl,(hlsave) ld de,(desave) ld bc,(bcsave) jp movcrs ; Set right margin ; setright: call savpos call statline ld a,(RTMARG) ld b,a call PRINT dc cr,'Right Margin (+/-): ' setrloop: ld a,b call PADC call CIN cp '+' jr z,setr1 cp '=' jr z,setr1 cp '-' jr z,setr2 cp '_' jr z,setr2 setrx: ld a,b ld (RTMARG),a call statline jp rstpos setr1: inc b setr1a: ld a,b cp 21 call c,limit1 cp 136 call nc,limit2 call print dc bs,bs,bs jr setrloop setr2: dec b jr setr1a limit1: ld b,20 ret limit2: ld b,135 ret ; Reformat text ; Ignores tabs ; Quits on "hard" CR, i.e. any CR not preceded by a wrdsep ; reform: call offline call reformat jp newscr ; Do the reformat in mem reformat: ld hl,(linptr) ld bc,(RTMARG) ; C = margin, B = trash refloop1: ld b,c ; Margin = down counter refloop2: ld a,(hl) cp eof ret z cp cr jr z,refmat1 inc hl djnz refloop2 ; Hit right margin, insert CR,LF at start of word ld a,(hl) cp cr jr z,refmat0a ; Line resonance? call wrdsep ; On a wordsep now? jr z,refmat3 ; Yes, go to start of next word call pwrdsep call nz,refmat2 ; Back up refmat0: pushm ex de,hl ld b,d ld c,e inc de inc de call endmove popm refmat0a: call clfill jr refloop1 ; Start new line ; Back up to start of this word refmat2: dec hl call pwrdsep jr nz,refmat2 ret refmat3: inc hl call wrdsep jr z,refmat3 cp cr jr z,refmat0a jr refmat0 ; Found early CR refmat1: call pwrdsep ret nz ; "Hard" CR cp '.' ; Ditto ret z cp '?' ret z pushm ; Close up CR,LF ex de,hl ; DE -> dest ld b,d ld c,e inc bc inc bc ; BC -> start of next line call endmove popm jr refloop2 ; Continue line ; ================================================================= ; ; D A T A ; ; ================================================================= dseg ; Keep these two together. They are double loaded into BC. n$txtlns: ds 1 ; Text lines nline: ds 1 ; Current line number ; width ds 1 ; Useable screen width estksav: ds 60 ; Incoming stack pointer estack: ds 2 ; Stack space down from here buftop: ds 2 ; Buffer top (allow a line of ovfl) eindex: ds 2 ; Buffer location for start of edit linptr: ds 2 ; Pointer to current line lcount: ds 1 ; Line buf line: ds lbufwid crsave: ds 1 hlsave: ds 2 desave: ds 2 bcsave: ds 2 end ;END EDIT.LIB