home *** CD-ROM | disk | FTP | other *** search
- Title UnMark.ASM -- Replaces TurboPower RELEASE Version 2.8
- ;v3.2 Toad Hall Tweak
-
- CSEG Segment Public Para ;Version 3.1 31-May-1989 - 03:10
- Assume CS:CSEG,DS:CSEG
-
- Org 0100h
- Main Proc Far
- Jmp Start
-
- UsageMsg DB 13,' ',9,10
- DB 'UnMark replaces RELEASE ver 2.8 by TurboPower Software',13,10,9
- DB '======================================================',13,10,9
- DB 'UnMark, like RELEASE, removes memory-resident programs',13,10,9
- DB 'and restores interrupt vectors to pre[F]Mark addresses.',13,10,10,9
- DB 'UnMark will UpDate the WATCH data area when WATCH has',13,10,9
- DB 'been installed ahead of the [F]Mark that is removed.',13,10,10,9
- DB 'UnMark also releases any Lotus/Intel expanded memory',13,10,9
- DB 'used by TSR programs which it releases.',13,10,10,9
- DB '/Keep [F]Mark and /No EMS RELEASE options are NOT',13,10,9
- DB 'implemented in UnMark. The UnMark syntax is:',13,10,10,9
- DB 'UNMARK [[FilePath\]MarkName] [Options]',13,10,10,9
- DB 9,'[/]?',9,'Write this Help screen',13,10,10,9
- DB 'Other Options MUST begin with a "/" character:',13,10,10
- DB 9,9,'/D',9,"Display MCBs",13,10
- DB 9,9,'/R',9,'Leave 8259 interrupt controller as is',13,10
- DB 9,9,'/S',9,'STUFF Keyboard Buffer (<=14 bytes+CR)'
-
- crlf DB 13,10,"$",8,32,26 ; You can >TYPE UnMark.COM
- emsID DB 'EMMXXXX0'
- markID DB '3.2 TSR ' ; ID of [F]Marks 7 bytes v3.2
- watchM DB 'WATCHER$' ; or Watch ID = 12 bytes
- header DB ' MCB Block Len User Release? $'
- trumsg DB ' True $'
- falmsg DB ' False $'
- mrkmsg DB '[F]Mark$PARAMETER'
- pgmmsg DB 'Program$'
- envmsg DB 'Environ$'
- trapmsg DB 'Trapped$'
- notfound DB 13,10,'NO '
- wasfound DB '[F]Mark found',13,10,"$"
- protected$ DB 13,10,'Protected Mark Encountered!',13,10,"$"
- fileError DB 13,10,'Error Reading FMark File!',13,10,"$"
- releasErr DB 13,10,'Release Failed!',13,10,'$'
- rammsg DB 'RAM bytes available: '
- free$ DB 6 DUP(' '),13,10,"$"
- flagd DB 0 ; Display MCBs IF Set
- flagr DB 0 ; Reset 8259 UNLESS Set
- ascii_tbl DB "!#$%&()-1234567890:'@ABCDEFGHIJKLMNOPQRSTUVWXYZ\^_{}~"
- NUMCHARS equ $ - ascii_tbl
- scanc_tbl label byte
- DB 2,4,5,6,8,10,11,12,2,3,4,5,6,7,8,9,10,11,39,40,3,30,48,46
- DB 32,18,33,34,35,23,36,37,38,50,49,24,25,16,19,31,20,22,47
- DB 17,45,21,44,43,7,12,26,27,41,0
- stuff_buf DW 15 DUP(1C0Dh)
- errlvl DW 4C00h ; Set for Program Exit
- pflaga DW 0 ; Set if Protected Mark
- mflaga DW 0 ; [F]Mark PSP When Found
- watchf DW 0 ; PSP of Watch When Found
- fmarkf DW 0 ; Set if FMark File Found
- MKPARM equ offset BUFFER ; Command [F]Mark Name
- mrklen DW ? ; Length of Name
- MCBBUF equ MKPARM + 40h ; MCB Table and [F]Mark
- mcbend DW ? ; End of MCB area
- VECTOR equ MCBBUF + 400h ; Interrupt Vectors, EGA and
- PARENT equ VECTOR + 418h ; ICA areas plus Parent Word
- EMSCNT equ PARENT + 2h ; EMS Handle Count and MAP
- EMSMAP equ EMSCNT + 2h ; from [F]Mark Storage
- ; <= 100h bytes for MAP
-
- Start: xor ax,ax ; Zero
- mov cx,2048 ; data
- mov di,MKPARM ; buffer
- rep stosw ; words
- mov di,MKPARM ; Set for [F]Mark ID
- mov si,81h ; Get Command
- call Ploop ; Parameter(s)
- mov ah,9 ; If NO ?
- jnc DoNew ; Then New Line
- mov dx,offset UsageMsg ; Else Display
- int 21h ; Syntax Message
- jmp Exit ; and Exit
-
- DoNew: mov dx,offset crlf ; Display
- int 21h ; New Line
- mov dx,MKPARM ; Calculate and
- sub di,dx ; Store [F]Mark
- mov mrklen,di ; Name Length
- mov ax,4300h ; If Attributes
- int 21h ; NOT Returned
- jc DoBuf ; Then NOT FMark
- mov fmarkf,CX ; Else Flag as FMark
-
- DoBuf: mov ah,52h ; Undocumented
- int 21h ; Function
- mov di,ES:[bx-2] ; obtains
- mov ES,di ; MCB of DOS
- inc di ; Config.Sys
- mov si,MCBBUF ; Initialize Source and
- xor bx,bx ; Basic Index Pointers
-
- MCBlp: add di,ES:[3] ; Advance so as to
- mov ES,di ; Point to MCB and
- inc di ; Next Paragraph
- mov [si+bx+0],es ; Store MCB
- mov dx,ES:[1] ; Get and Store
- mov [si+bx+2],dx ; Block Address
- mov ax,ES:[3] ; and Block
- mov [si+bx+4],ax ; Length
- call DoFlags ; Set Appropriate Flags
- add bx,8 ; Advance to Next and
- cmp byte ptr ES:[0],"Z" ; Loop Until Last MCB
- jne MCBlp
-
- ;v3.2 push DS ; Restore Extra Segment
- ; pop ES ; Register to DATA
- mov ax,DS ;restore ES to data v3.2
- mov ES,ax
- mov mcbend,si ; Initialize MCB buffer end
- add mcbend,bx ; Adjust buffer end for length
- mov ax,mflaga ; If NO [F]Mark
- or ax,ax ; Name Matched
- jz CkLast ; Then Try Last
- cmp ax,pflaga ; Else If Below Protected
- jc IsPME ; Then Protected Error Exit
-
- CkLast: mov di,si ; Point to Buffer
- mov ax,-1 ; Find [F]Mark
- mov cx,bx ; for Release
- shr cx,1 ; In MCB Words
- repne scasw ; If None Found Yet
- jne DoLast ; Then Assume Last Mark
- jmp DoMark ; Else Get [F]Mark Data
-
- DoLast: cmp word ptr mrklen,0 ; If [F]Mark
- jnz NoMark ; Command Name
-
- mov di,mcbend ; Or If Scan MCBs
- std ; backwards finds
- mov cx,bx ; NO [F]Mark
- repne scasb ; Marked
- cld ; Then NO [F]Mark
- jne NoMark ; Found Error Exit
-
- sub di,5 ; Else Point to
- mov bx,di ; [F]Mark Record
- sub bx,si ; With Basic Index
- mov di,MKPARM ; Set Destination
- push si ; Preserve
- push DS ; Source
- mov DS,[si+bx+2] ; Point to and
- mov si,81h ; Get Command
- call Ploop ; [F]Mark Name
- pop DS ; Restore
- pop si ; Source
- mov cx,di ; If NO [F]Mark
- sub cx,MKPARM ; Command Length
- jz ReLast ; Then Release Mark
-
- mov di,MKPARM ; Else Scan
- mov al,"!" ; for "!"
- repne scasb ; If Found
- je IsPME ; Then Protected Error Exit
- jmp short NoMark ; Else Is Named Mark
-
- ReLast: mov ax,[si+bx+2] ; Set the [F]Mark
- mov mflaga,ax ; PSP Address and
- mov mrklen,ax ; use as Length
- mov word ptr [si+bx+6],-1 ; Flag for Release
- mov ES,[si+bx+0] ; Re-Set Registers
- mov di,[si+bx+2] ; and Re-Enter MCBs
- add bx,8 ; Loop after [F]Mark to
- jmp MCBlp ; Release subsequent MCBs
-
- IsPME: cmp flagd,0FFh ; If NO Display MCBs Flag
- jne DoPME ; Then Skip to Message
- call DoDeBug ; Else Show MCBs
- DoPME: mov dx,offset protected$ ; Error Exit with
- mov byte ptr errlvl,1 ; Error Level 1 and
- jmp Show ; Protected [F]Mark Message
-
- NoMark: cmp flagd,0FFh ; If NO Display MCBs Flag
- jne DoNFM ; Then Skip to Message
- call DoDeBug ; Else Show MCBs
- DoNFM: mov dx,offset notfound ; Error Exit with
- mov byte ptr errlvl,2 ; Error Level 2 and
- jmp short Show ; Not Found Message
-
- DoFErr: mov ah,3Eh ; Close the File
- int 21h ; Handle If Possible
- mov dx,offset fileError ; Reading [F]Mark File
- mov byte ptr errlvl,3 ; Error Level 3 and
- jmp short Show ; Exit without Release
-
- DoMark: mov dx,di ; Save Pointer and
- mov bx,ES:[di+2] ; Block of [F]Mark
- DMloop: sub di,8 ; If Down to
- cmp si,di ; MCBBUF start
- jnc IfMark ; Then Do File or Mark
- mov ax,ES:[di+2] ; Else If Block
- mov cx,ES:[di] ; Compared to
- inc cx ; MCB + 1
- cmp ax,cx ; Shows
- jz DMloop ; Program
- or ax,ax ; Or If Trapped
- jz DMloop ; Block Or If
- cmp ax,bx ; Less Than [F]Mark
- jc DMloop ; Then Continue Look-Back
- mov byte ptr ES:[di+7],0FFh ; Else Mark Environment
- jmp short DMloop ; Loop-Back Until Start
-
- IfMark: mov di,dx ; Restore Pointer to [F]Mark
- cmp word ptr fmarkf,0 ; If NOT File Mark
- jz IsMark ; Then is Memory
-
- mov dx,MKPARM ; Else Open File
- mov ax,3D00h ; for Read Only
- int 21h ; If Open Fails
- jc DoFErr ; Then File Error Exit
- mov dx,VECTOR ; Else Copy Interrupt
- mov cx,051Ch ; EGA, ICA, Parent and
- mov bx,ax ; EM Handle Count from
- mov ah,3Fh ; File Mark file
- int 21h ; If file Read Fails
- jc DoFErr ; Then File Error Exit
- mov ah,3Eh ; Else Close the
- int 21h ; File Handle and
- jmp short MkExit ; Check DeBug Flag
-
- IsMark: mov DS,[di-6] ; Get Memory data
- mov si,0120h ; Copy Mark Interrupts
- mov cx,051Ch ; EGA,ICA, Parent and
- mov di,VECTOR ; EMS Information
- rep movsb ; Into data buffer
- mov cx,CS ; Restore v3.2
- mov DS,cx ; Segment v3.2
- MkExit: cmp flagd,0FFh ; If NO Flag
- mov dx,offset wasfound ; Then Show
- jne Show ; only Result
- call DoDeBug ; Else MCBs also
- Show: mov ah,9 ; Display
- int 21h ; Message
- mov si,mcbend ; Start at the
- sub si,8 ; UnMark Block
- mov di,MCBBUF ; Working Toward
- add di,16 ; DOS Environment
- mov dx,[si+2] ; Get UnMark Address
- mov ax,[si+4] ; and Free at UnMark
- cmp dx,[si-6] ; Unless Contiguous
- jne ChkErr ; UnMark Environment
- inc ax ; Don't Include MCB
- ChkErr: cmp byte ptr errlvl,0 ; If an UnMark Error
- jnz FreeOk ; Then Free is Unchanged
-
- LookLp: sub si,8 ; Look-Back Loop
- mov cx,[si+2] ; If Block Address
- cmp cx,dx ; IS Same as UnMark
- je EndChk ; Then Don't Add
- or cx,cx ; Else If NOT Trapped
- jnz LookCk ; Then Check If Marked
- cmp byte ptr [si+15],0 ; Else If Marked Above
- jnz LookAd ; Then Add to Free
- jmp short EndChk ; Else Don't Add
-
- LookCk: cmp byte ptr [si+7],0 ; If Block NOT Marked
- jz EndChk ; Then Don't Add
- LookAd: add ax,[si+4] ; Else Add Length
- inc ax ; and MCB to Free
- EndChk: cmp di,si ; Until Just Above
- jc LookLp ; DOS Environment
-
- FreeOk: xor dx,dx ; Clear Extension
- mov dl,ah ; Free RAM Equals
- mov cl,4 ; Free Paragraphs
- shr dx,cl ; Converted to
- shl ax,cl ; DD bytes in DX:AX
- mov bx,offset free$+6 ; Store Free as
- mov cx,10 ; Decimal Digits
- NexDig: div cx ; Store each
- or dx,30h ; ASCII digit
- dec bx ; Right to Left
- mov [bx],dl ; Until
- xor dx,dx ; both DX
- or ax,ax ; and AX
- jnz NexDig ; are 0
-
- mov ah,9 ; Display
- mov dx,offset rammsg ; RAM Bytes Free
- int 21h
- cmp byte ptr errlvl,0 ; If NO [F]Mark Error
- jz ChkEMS ; Then Continue
- jmp Exit ; Else Error Exit
-
- ChkEMS: mov ax,3567h ; Locate Driver
- int 21h ; Interrupt
- mov di,0Ah ; Address
- ;v3.2 lea si,emsID ; If Name
- mov si,offset emsID ;if name v3.2
- mov cx,8 ; 'EMMXXXX0'
- rep cmpsb ; Is NOT Found
- mov ax,CS ; After Extra Segment v3.2
- mov ES,ax ; Register is Restored v3.2
- jne EndEMS ; Then NO EMS
-
- ;v3.2 mov di,EMSMAP ; Else Point to
- ;v3.2 add di,100h ; Next Map Area
- mov di,EMSMAP+100H ;else point to next map area v3.2
- mov ah,4Dh ; Get Current
- int 67h ; Handle Map
- or ah,ah ; If Function Fails
- jnz EndEMS ; Then EMS Broken
- mov si,EMSCNT ; Else If [F]Mark
- lodsw ; Handle Count Is
- mov cx,bx ; Not Less Than
- cmp ax,bx ; Current Count
- jnc EndEMS ; Then EMS NOT Used
-
- EMSHlp: mov dx,ES:[di] ; Else Compare
- cmpsw ; Maps and Release
- cmpsw ; Handle(s) NOT in
- je lpEMSH ; [F]Mark Map Using
- mov ah,45h ; Deallocate Handle
- int 67h ; EMS Function
- or ah,ah ; If Ok AND More
- lpEMSH: loopz EMSHlp ; Then Continue
-
- mov byte ptr errlvl,ah ; Else EMS Done
- EndEMS: mov ax,watchf ; If WATCH
- or ax,ax ; NOT Found
- jz WatchX ; Then Skip
-
- mov ES,ax ; Else Point
- mov di,218h ; short of WATCH
- mov dx,-1 ; Vector Change Area
- mov ax,mflaga ; Looking for [F]Mark
- mov cx,620h
- UCloop: add di,8 ; If Reach End of
- cmp di,cx ; Vector Change Area
- jnc WatchX ; Then NO Changes
- cmp ES:[di],dx ; Else If NOT PSPid
- jnz UCloop ; Or If PSP is NOT
- cmp ES:[di+2],ax ; PSP of [F]Mark
- jnz UCloop ; Then Keep Looking
-
- mov dx,di ; Else Calculate
- sub dx,220h ; and store new
- mov ES:[104h],dx ; vpos offset and
- xor al,al ; Null-out
- sub cx,di ; remaining
- rep stosb ; Vector Change Area
- mov si,VECTOR ; Copy Interrupt
- mov cx,200h ; Vector words
- mov di,0A20h ; Into WATCH prevv
- rep movsw ; Current Vector Table
- WatchX:
- ;v3.2 push CS ; Restore Extra
- ;v3.2 pop ES ; Segment Register
- mov di,CS ;restore ES v3.2
- mov ES,di ;v3.2
- mov di,MCBBUF ; Prepare to Kill File(s)
- FileLp:
- ;v3.2 push CS ; Insure Data Segment
- ;v3.2 pop DS ; Register in Program
- mov ax,CS ;insure DS v3.2
- mov DS,ax ;v3.2
- mov cx,mcbend ; Calculate
- sub cx,di ; Number of
- shr cx,1 ; Words to
- mov ax,-1 ; Scan for Marked
- repne scasw ; [F]Mark Blocks
- jne CheckR ; Until all Done
-
- mov DS,ES:[di-6] ; Point to Mark
- mov si,81h ; Command Name
- xor bx,bx ; Set Pointer to
- mov bl,DS:[si-1] ; Length of Name
- xor ch,ch ; Make ASCIIZ and
- mov cl,DS:[si+bx] ; Save Previous
- mov DS:[si+bx],ch ; Name Command End
- mov ah,41h ; Delete
- mov dx,82h ; File(s)
- int 21h ; Restore
- mov DS:[si+bx],cl ; Ending
- jmp short FileLp ; Loop Until Done
-
- CheckR: cmp flagr,0 ; If Leave 8259 as is
- jnz UnMark ; Then Skip Procedure
- call Rst8259 ; Else Reset 8259
- UnMark: mov si,mcbend ; Work between
- sub si,8 ; UnMark Program
- ;v3.2 mov bp,MCBBUF ; and Master
- ;v3.2 add bp,8 ; Environment
- mov bp,MCBBUF+8 ; and Master Environment v3.2
- Loop49: sub si,8 ; If Down to Master
- cmp si,bp ; Environment
- je Result ; Then Done Releasing
-
- mov ax,[si] ; Else If NOT
- inc ax ; Marked for
- cmp byte ptr [si+7],0FFh ; Release
- jne Loop49 ; Then Loop
- mov ES,ax ; Else If
- mov ah,49h ; Released
- int 21h ; w/o error
- jnc Loop49 ; Then Continue
-
- mov byte ptr errlvl,al ; Else Set Error
- mov ah,9 ; and Display
- mov dx,offset releasErr ; Error Message
- int 21h
- Result: cmp byte ptr errlvl,0 ; If NO Error
- jz SetPSP ; Then Continue
- int 19h ; Else ReBoot
- SetPSP:
- ;v3.2 push CS ; Restore Extra
- ;v3.2 pop ES ; Segment Register
- mov di,CS ;restore ES v3.2
- mov ES,di ;v3.2
- mov di,0Ah ; Set PSP from
- ;v3.2 mov si,VECTOR ; Vectors for
- ;v3.2 add si,88h ; Interrupts
- mov si,VECTOR+88H ;vectors for interrupts v3.2
- mov cx,6 ; 22h, 23h,
- rep movsw ; and 24h
- mov si,PARENT ; Get Parent Word
- movsw ; and Take Command
- xor di,di
- mov ES,di ; Restore
- mov si,VECTOR ; Interrupt
- ;v3.2 mov cx,1024 ; Vectors
- mov cx,1024/2 ; vectors (as words) v3.2
- cli ;(probably unneeded) v3.2
- ;v3.2 rep movsb
- rep movsw ;as words v3.2
- sti
- add di,0A8h ; Restore EGA
- ;v3.2 mov cx,8 ; Information
- ;v3.2 rep movsb
- mov cx,4 ;information (as words) v3.2
- rep movsw ;v3.2
- add di,40h ; Restore Inter-
- mov cx,8 ; Communications
- rep movsw ; Area Information
-
- cmp word ptr stuff_buf,1C0Dh; If Nothing to Stuff
- je Exit ; Then Exit
- call StufKey ; Else Stuff
-
- Exit: mov ax,errlvl ; Set Error Level
- int 21h ; and Exit to DOS
- Main EndP
-
- Ploop Proc
- lodsb ; Get a Byte
- cmp di,MKPARM ; If Stuffing
- jc Stuff ; Then Stuff
- cmp al,"/" ; Else If Switch
- je Parms ; Then Get Parameter
- cmp al,"?" ; Else If Question
- je DoHelp ; Then Give Help
- cmp al,13 ; Else If End Byte
- je Pexit ; Then Exit Parsing
- cmp al,"!" ; Else If Space or Below
- jc Ploop ; Then Ignore Character
- stosb ; Else Store ID Name
- jmp short Ploop ; Until [F]Mark ID ends
-
- Parms: lodsb ; Get Byte After Switch
- cmp di,MKPARM ; If NOT Stuffing
- jnc ParaQ ; Then Ready to Check
- pop di ; Else Even the Stack
- ParaQ: cmp al,"?" ; If Question
- je DoHelp ; Then Give Help
-
- and al,5Fh ; Else UP-case
- cmp al,"D" ; If NOT "D"eBug
- jne ParaR ; Then Check "R"eset
- mov flagd,0FFh ; Else Set D Flag
- ParaR: cmp al,"R" ; If NOT "R"eset 8259
- jne ParaS ; Then Check Stuff
- mov flagr,0FFh ; Else Set R Flag
- ParaS: cmp al,"S" ; If NOT "S"tuff
- jne Ploop ; Then Get Next Byte
- push di ; Else Preserve Pointer
- mov di,offset stuff_buf ; While Storing Stuff
- mov cx,14 ; Up to 14 bytes plus
- jmp short Ploop ; Ending Carriage Return
-
- Stuff: cmp al,"!" ; If Space Or Less
- jc Sexit ; Or If Another
- cmp al,"/" ; Switch While Stuffing
- je Sexit ; Then Exit Stuffing
-
- cmp al,"a" ; Else Insure
- jc UCexit ; Alphabetic
- cmp al,"z" ; Characters
- ja UCexit ; Converted to
- and al,5Fh ; UPPERcase
- UCexit: push cx ; Preserve Limit and
- push di ; Position in stuff_buf
- mov cx,NUMCHARS ; Set Scan Count and
- mov bx,offset scanc_tbl ; Indices to Scan Codes
- mov di,offset ascii_tbl ; Versus ASCII Codes
- sub bx,di ; Adjust Scan Code
- repne scasb ; Pointer for Position in
- add bx,di ; ASCII Character Table
- mov ah,[bx-1] ; Get Scan Code and
- pop di ; Restore Pointer and
- pop cx ; Stuff Character Counter
- or ah,ah ; If Invalid Code
- jz Sexit ; Then Exit Stuffing
- stosw ; Else Store Code/Byte
- loop Ploop ; Until End of Stuffing
-
- Sexit: pop di ; Even Stack and Back-Up
- dec si ; Input In Case of Switch
- cmp al,"/" ; If If End With Switch
- je Ploop ; Then Resume Parsing
- cmp al,13 ; Else If End of Input
- je Pexit ; Then Exit Normally
- DoHelp: stc ; Else Set CY for Help
-
- Pexit: ret
- Ploop EndP
-
- DoFlags Proc
- push si ; Preserve
- push di ; Pointers and
- push ES ; Segment Register
- mov bp,di ; Copy for Comparisons
- sub dx,di ; If a Program
- jz ChkPgm ; Then Check It
-
- xor dx,dx ; Else Zero Flags
- ChkRel: cmp word ptr mflaga,0 ; If NO [F]Mark Yet
- jz ExitDF ; Then NO Release Flag
- mov dh,0FFh ; Else Mark for Release
- ExitDF: jmp short DFexit
-
- ChkPgm: mov ES,di ; Look in
- mov di,62h ; Program
- mov cx,7 ; for ID of
- mov si,offset markID ; an [F]Mark
- rep cmpsb
- mov di,81h ; If an [F]Mark
- je ChkMrk ; Then Check Name
- mov si,offset mrkmsg+8 ; Else Check for
- mov di,108h ; TurboPower
- mov cx,9 ; "PARAMETER"
- rep cmpsb
- mov di,81h ; If TurboPower
- je ChkMrk ; Then Check Name
- mov cx,11 ; Else If NOT TSR
- mov si,offset markID+4 ; WATCHER Name
- rep cmpsb ; "TSR WATCHER"
- jne ChkRel ; Then Check Release
- mov watchf,bp ; Else Store Address
- jmp short ChkRel
-
- ChkMrk: mov dl,0FFh ; Flag as [F]Mark
- mov cl,ES:[di-1] ; If NO Length
- jcxz Chk4MF ; Then NO Protect
-
- push di ; Else Save Name
- push cx ; and Length
- mov al,"!" ; Scan for
- repne scasb ; Protected
- pop cx ; If NOT
- pop di ; Protected
- jne Chk4MF ; Then Check Mark Flag
- mov pflaga,bp ; Else Set Protected Flag
- Chk4MF: cmp word ptr mflaga,0 ; If NO Release [F]Mark
- jz DoName ; Then Check This One
- mov dh,0FFh ; Else Mark for Release
- jmp short DFexit
-
- DoName: dec cx ; Assume space
- cmp mrklen,cx ; If NOT length of
- mov si,MKPARM ; Parameter Name
- jne DFexit ; Then Check Release
-
- FNloop: inc di ; Else Get
- lodsb ; Next Byte
- cmp pflaga,bp ; If Protected [F]Mark
- jz FNBcmp ; Then Compare Exact
- or al,20h ; Else Insure lower
- FNBcmp: sub al,ES:[di] ; If Name Bytes Match
- je loopFN ; Then Compare Until
- cmp pflaga,bp ; Else If Protected
- jz DFexit ; Then MCB Flag Exit
- cmp al,20h ; Else If Only Case
- loopFN: loope FNloop ; Then Compare Until
- jne DFexit ; Fail or Match
- Match: mov dh,0FFh ; Mark [F]Mark and
- mov mflaga,bp ; Subsequent MCBs
- ; for Release
- DFexit: pop ES ; Restore Segment
- pop di ; Destination and
- pop si ; Source Pointers
- mov [si+bx+6],dx ; Set MCB Flags
- ret
- DoFlags EndP
-
- DoDeBug Proc
- push dx ; Preserve Message
- mov ah,9 ; Display
- mov cx,2 ; two sets of
- mov dx,offset header ; DeBug Headers
- ShoHdr: int 21h
- loop ShoHdr
- mov si,MCBBUF ; Point to Array
- DoMCBs: mov cx,2 ; Two Members
- mov dx,offset crlf ; per each
- int 21h ; New Line
-
- ShoMCB: push cx ; Preserve Set Count
- mov bl,[si+1] ; Get MCB High Byte
- call ShowVal ; and Display ASCII
- mov bl,[si+0] ; Get MCB Low Byte
- call ShowVal ; and Display ASCII
- mov dl," " ; Add a Space
- int 21h
- mov bl,[si+3] ; Get Block High Byte
- call ShowVal ; and Display ASCII
- mov bl,[si+2] ; Get Block Low Byte
- call ShowVal ; and Display ASCII
- mov dl," " ; Add a Space
- int 21h
- mov bl,[si+5] ; Get Length High Byte
- call ShowVal ; and Display ASCII
-
- mov bl,[si+4] ; Get Length Low Byte
- call ShowVal ; and Display ASCII
- mov dl," " ; Add a Space
- int 21h
- mov dx,offset watchM ; If Watch
- mov ax,watchf ; PSP Block
- dec ax ; minus one
- cmp ax,[si] ; Matches MCB
- je ShoUsr ; Then is Watch
- mov dx,offset mrkmsg ; Else If [F]Mark
- cmp byte ptr [si+6],0FFh ; flag is set
- je ShoUsr ; Then [F]Mark
- mov dx,offset pgmmsg ; Else If Block
- mov bx,[si+2] ; is the next
- dec bx ; paragraph
- cmp bx,[si+0] ; after MCB
- je ShoUsr ; Then Program
- mov dx,offset envmsg ; Else Environ
- cmp bx,-1 ; Unless
- jne ShoUsr ; Block is
- mov dx,offset trapmsg ; Trapped
- ShoUsr: mov ah,9 ; Display
- int 21h ; User
- mov dx,offset trumsg ; If Marked
- cmp byte ptr [si+7],0FFh ; for Release
- je ShoRel ; Then True
- mov dx,offset falmsg ; Else False
- ShoRel: int 21h ; Message
- pop cx ; Restore Counter
- add si,8 ; If NOT at
- cmp si,mcbend ; End of MCBs
- loopne ShoMCB ; Then Continue
- jne DoMCBs ; Until All Done
-
- pop DX ; Restore Message
- ret
- DoDeBug EndP
-
- ;v3.2 Now doing calcs in AL (faster)
- ShowVal Proc
- mov cl,4 ; Set Divisor 16
- mov ah,2 ; for Show Byte
- mov al,bl ; Copy the Byte
- and al,0F0h ; Isolate High
- shr al,cl ; Nibble as
- add al,30h ; ASCII
- cmp al,3Ah ; If Decimal
- jc SV1 ; Then Show Dec
- add al,7 ; Else Show Hex
- SV1: mov dl,al ;v3.2
- int 21h
- mov al,bl ; Copy the Byte
- and al,0Fh ; Isolate Low
- add al,30h ; ASCII Nibble
- cmp al,3Ah ; If Decimal
- jc SV2 ; Then Show Dec
- add al,7 ; Else Show Hex
- SV2: mov dl,al
- int 21h
- ret
- ShowVal EndP
-
- StufKey Proc
- mov ah,1 ; If KeyBoard Buffer
- int 16h ; is Clear of Keys
- jz Set_SI ; Then Ready to Stuff
- xor ah,ah ; Else Read Scan Code
- int 16h ; Code and Character
- jmp short StufKey ; Until Buffer Clear
-
- Set_SI: mov si,offset stuff_buf ; Point to StufString
- mov ax,40h ; Set Segment of
- mov ES,ax ; Buffer and its
- mov ax,ES:[80h] ; Beginning Word
- mov di,ax ; As Pointers to
- sub di,4 ; Head and Tail
- cli ; Hold Interrupts
- stosw ; While Initializing
- mov bp,di ; Key Buffer Head, Tail
- stosw ; and Key Word Contents
- SKloop: lodsw ; Stuff stuff_buf Stuff
- stosw ; Into Key Buffer and
- add word ptr ES:[bp],2 ; Adjust Tail Until
- cmp ax,1C0Dh ; Carriage
- jne SKloop ; Return
- push DS ; Restore Extra
- pop ES ; Segment Register
- sti ; Allow Interrupts
- ret
- StufKey EndP
-
- Rst8259 Proc ; RESET THE 8259 INTERRUPT CONTROLLER CHIP - Rick Housh
- push ES ; Point Extra Segment to
- mov ax,-1 ; Machine ID byte at
- mov ES,ax ; Offset 14, in ROM BIOS
- mov al,Byte Ptr ES:[0Eh] ; Store machine ID byte
- pop ES ; PC=0FFh, XT=0FEh, AT=0FCh
- cli ; Interrupts off
- cmp al,0FCh ; If ID Byte = 0FCh
- jz RstAT ; Then Reset AT
- cmp al,0FEh ; Else If NOT PC/XT
- jc RstX ; Then phooey on PC Jr
- ; and NON-Compatibles
- RstPC: in al,21h ; Else Get and Save
- mov ah,al ; Current Interrupt
- mov al,13h ; Mask for PC or XT
- out 20h,al
- jmp short $+2 ; Delay
- mov al,8 ; Set up main vector number
- out 21h,al
- jmp short $+2
- mov al,9
- out 21h,al
- jmp short $+2
- mov al,ah ; Restore mask and reset
- out 21h,al ; previous interrupt state
- jmp Short RstX ; Interrupts back on and exit
-
- RstAT: xor al,al ; For AT, turn off any
- out 0F1h,al ; 80287 math coprocessor
- jmp short $+2 ; Delay
- in al,21h ; Get current interrupt mask
- mov ah,al ; and save it
- mov al,11h
- out 20h,al
- jmp short $+2
- mov al,8 ; Set up main vector number
- out 21h,al
- jmp short $+2
- mov al,4
- out 21h,al
- jmp short $+2
- mov al,1
- out 21h,al
- jmp short $+2
- mov al,ah ; Restore mask, reset
- out 21h,al ; previous interrupt state
- jmp short $+2
-
- RstSlv: in al,0A1h ; For slave 8259,
- mov ah,al ; Get and save current Mask
- mov al,11h
- out 0A0h,al
- jmp short $+2 ; Delay
- mov al,70h
- out 0A1h,al
- jmp short $+2
- mov al,2
- out 0A1h,al
- jmp short $+2
- mov al,1
- out 0A1h,al
- jmp short $+2
- mov al,ah ; Restore mask, reset
- out 0A1h,al ; previous interrupt state
- RstX: sti ; Interrupts back on
- Ret ; Exit
- Rst8259 EndP
-
- align 16
- BUFFER equ $
-
- CSEG EndS
- End Main