SWAGOLX.EXE (c) 1993 GDSOFT ALL RIGHTS RESERVED 00011 INTERRUPT HANDLING ROUTINES 1 05-28-9313:48ALL SWAG SUPPORT TEAM BITSTUFF.PAS IMPORT 40 {π Well Percy (or is it Kerry?), I see that the regular crowd here haveπ shown you how bit-level thingys work. So, I'll give you a workingπ example, including a Procedure to display the binary notation of anyπ Integer, so you can play With the inFormation they've given you. Theπ following Program reads & displays info from the equipment list Wordπ (Note: I've made [lazy] use of global Variables, do not emulate)...π}π(*******************************************************************)πProgram BitsNBytes; { ...or Digital Road Kill }πUsesπ Dos; { import Intr() and Registers }πVarπ NumberFDD, { number of floppy drives }π InitVMode, { intial video mode }π COMcount, { number of serial ports }π LPTcount : Byte; { number of Printer ports }π Is8087, { math copro installed? }π IsMouse, { pointing device installed? }π IsDMA, { DMA support installed? }π IsGame, { game port installed? }π IsModem : Boolean; { internal modem installed? }π EqWord : Word; { the equipment list Word }π Reg : Registers; { to access CPU Registers }π{-------------------------------------------------------------------}πFunction BitSet(AnyWord : Word; BitNum : Byte) : Boolean;π { return True if bit BitNum of AnyWord is 1, else False if it's 0 }πbeginπ BitSet := (BitNum in [0..15]) and ODD(AnyWord SHR BitNum);πend {BitSet};π{-------------------------------------------------------------------}πProcedure WriteBitWord( AnyWord : Word ); { show Word as binary }πVarπ BinString : String[16]; { represent binary bits }π MaxBit, { max number of bits }π BitNum : Byte; { bits 0..15 }πbeginπ BinString := '0000000000000000'; { default to 0 }π MaxBit := Length(BinString); { total bit count (16) }π For BitNum := 0 to PRED(MaxBit) do { process bits (0..15) }π if BitSet(AnyWord, BitNum) thenπ INC(BinString[MaxBit - BitNum]);π Write( BinString ); { Write the binary Form }πend {WriteBitWord};π{-------------------------------------------------------------------}πProcedure ProcessEquipList; { parse equipment list Word EqWord }πVarπ BitNum : Byte; { to check each bit }π EBitSet : Boolean; { True if a BitNum is 1, else False }πbeginπ For BitNum := 0 to 15 doπ begin { EqWord has 16 bits }π EBitSet := BitSet(EqWord,BitNum); { is this bit set? }π Case BitNum of { each bit has meaning }π 0 : if EBitSet then { if EqWord.0 is set }π NumberFDD := (EqWord SHR 6) and $3 + 1π elseπ NumberFDD := 0;π 1 : Is8087 := EBitSet; { if math co-pro found }π 2 : IsMouse := EBitSet; { if pointing device }π 3 : ; {reserved, do nothing}π 4 : InitVMode := (EqWord SHR BitNum) and $3;π 5..7 : ; {ignore}π 8 : IsDMA := EBitSet;π 9 : COMcount := (EqWord SHR BitNum) and $7;π 10,11 : ; {ignore}π 12 : IsGame := EBitSet;π 13 : IsModem := EBitSet;π 14 : LPTcount := (EqWord SHR BitNum) and $7;π 15 : ; {ignore}π end; {Case BitNum}π end; {For BitNum}πend {ProcessEquipList};π{-------------------------------------------------------------------}πFunction Maybe(Truth : Boolean) : String;πbeginπ if not Truth thenπ Maybe := ' not 'π elseπ Maybe := ' IS ';πend {Maybe};π{-------------------------------------------------------------------}πbeginπ Intr( $11, Reg );π EqWord := Reg.AX;π WriteLn;π Write('Equipment list Word: ',EqWord,' decimal = ');π WriteBitWord( EqWord );π WriteLn(' binary');π WriteLn;π ProcessEquipList;π WriteLn('Number of floppies installed: ', NumberFDD );π WriteLn('Math-coprocessor',Maybe(Is8087),'installed' );π WriteLn('PS/2 Mouse',Maybe(IsMouse),'installed' );π Write('Initial video mode: ',InitVMode,' (' );π Case InitVMode ofπ 0 : WriteLn('EGA, VGA, PGA)');π 1 : WriteLn('40x25 colour)');π 2 : WriteLn('80x25 colour)');π 3 : WriteLn('80x25 monochrome)');π end;π WriteLn('DMA support',Maybe(IsDMA),'installed' );π WriteLn('Number of COMs installed: ',COMcount );π WriteLn('Game port',Maybe(IsGame),'installed' );π WriteLn('IBM Luggable modem',Maybe(IsModem),'installed');π WriteLn('Number of Printer ports: ',LPTcount );πend {BitsNBytes}.π(*******************************************************************)ππ 2 05-28-9313:48ALL SWAG SUPPORT TEAM CLOCK1.PAS IMPORT 22 {πCARLOS BEGUIGNEπ}πProgram ClockOnScreen;ππ{$R-,V-,S-,M 1024, 0, 0ππ ClockOnScreen - Installs resident clock on upper right corner of screen.ππ{$IFOPT S+ }ππ{π You must disable stack checking here, since a Runtime error 202 willπ be generated whenever the stack Pointer (as returned by SPtr) is likelyπ to drop below 1024.π}πUsesπ Dos, Crt;πConstπ Offset = $8E; { Line 1, Column $8E/2 = 71 }π TimerTick = $1C; { Timer interrupt }π black = 0;π gray = 7;π EnvSeg = $002C; { Segment of Dos environment }π ColourSeg = $B800; { Segment of colour video RAM }π MonoSeg = $B000; { Segment of monochrome ideo RAM }π CrtSegment : Word = ColourSeg;ππTypeπ ScreenArray = Array[0..7] of Recordπ number, attribute : Char;π end;ππ ScreenPtr = ScreenArray;ππVarπ VideoMode : Byte Absolute $0000:$0449;π Screen : ^ScreenPtr; { Physical screen address }π ClockColour : Char;π Int1CSave : Procedure;ππProcedure ShowTime; Interrupt;πConstπ separator = ':';πVarπ ThisMode : Byte;π Time : LongInt;π i : Integer;π BIOSTicker : LongInt Absolute $0000:$046C;ππ Procedure DisplayDigit(offset : Integer; digit : Integer);π beginπ Screen^ [offset].number := Chr(digit div 10+Ord('0'));π Screen^ [offset+1].number := Chr(digit mod 10+Ord('0'));π end; { DisplayDigit }ππbeginπ ThisMode := VideoMode;π if not ((ThisMode = 2) or (ThisMode = 3) or (ThisMode = 7)) Thenπ Exit; { Do not popup in a Graphic mode }π For i := 0 to 7 Doπ Screen^[i].attribute := ClockColour;π Time := (1365*BIOSTicker) div 24852;π DisplayDigit(0, Time div 3600); { hours }π Screen^[2].number := separator;π Time := Time mod 3600;π DisplayDigit(3, Time div 60); { minutes }π Screen^[5].number := separator;π DisplayDigit(6, Time mod 60); { seconds }π Inline($9C); { PUSHF }π Int1CSave;πend; { ShowTime }ππProcedure Release(segment : Word);πInLine(π $07/ { POP ES ; get segment of block to release }π $B4/$49/ { MOV AH, 49h ; Free Allocated Memory }π $CD/$21); { INT 21h ; call Dos }ππbegin { ClockOnScreen }π if VideoMode = 7 Thenπ CrtSegment := MonoSeg;π ClockColour := Chr(gray*16+black); {display video attribute }π Screen := Ptr(CrtSegment, Offset);π GetIntVec(TimerTick, @Int1CSave);π SetIntVec(TimerTick, @ShowTime);π Release(MemW[PrefixSeg:EnvSeg]); {Release the environment }π Keep(0);π readln;πend. { ClockOnScreen }ππ 3 05-28-9313:48ALL SWAG SUPPORT TEAM INTREXAM.PAS IMPORT 7 Okay, well, For the most part, calling an interrupt from TP is fairlyπsimple. I'll use Interrupt 10h (service 0) as an example:ππProcedure CallInt;πVarπ Regs : Registers;πbeginπ Regs.AH := 0; { Specify service 0 }π Regs.AL := $13; { Mode number = 13 hex, MCGA 320x200x256 }π Intr($10,Regs); { Call the interrupt }πend;ππThis would shift the screen to the MCGA Graphics mode specified. Now,πit's easier to call this in BAsm (built-in Assembler):ππProcedure CallInt; Assembler;πAsmπ MOV AH,0 { Specify service 0 }π MOV AL,13h { Mode number = 13 hex, MCGA 320x200x256 }π inT 10h { Call the interrupt }πend;ππ 4 05-28-9313:48ALL SWAG SUPPORT TEAM ISRINFO.PAS IMPORT 6 {πSEAN PALMERππ> Does anyone know how to Write an ISR (interrupt service routine) that willπ> continue With the interrupt afterwards. EX: if you Write an ISR that trapsπ> the mouse Int 33h but let the mouse still operate.ππTry:π}ππVarπ oldMouseHook : Procedure;ππProcedure mouseHook(AX,BX,CX,DX,SI,DI,DS,ES,BP); interrupt;πbeginππ {Your stuff goes here}π {make sure it doesn't take TOO long!}ππ Asmπ pushF;π end; {simulate an interrupt}ππ oldMouseHook; {call old handler}πend;ππ{ to install: }ππ getIntVec($33,@oldMouseHook);π setIntVec($33,@mouseHook);ππ{ to deinstall: }ππ setIntVec($33,@oldMouseHook);ππ 5 05-28-9313:48ALL SWAG SUPPORT TEAM REG1.PAS IMPORT 6 π Registers DemoππPB> Procedure GetScreenType (Var SType: Char);πPB> VarπPB> Regs: Registers;πPB> beginπPB> Regs.AH := $0F;πPB> Intr($10, Regs);πPB> if Regs.AL = 7 thenπPB> sType := 'M'; <<<<<πPB> elseπPB> sType := 'C';πPB> end;ππ This Procedure would be ideal For a Function...π Function GetScreenType:Char;π ...π if Regs.AL=7 thenπ GetScreenType := 'M'π elseπ GetScreenType := 'C';π ...π 6 05-31-9308:06ALL SWAG SUPPORT TEAM Critical Error Trap IMPORT 50 ==============================================================================π BBS: -=- Edge of the Century -=-π To: DANIEL KEMPTON Date: 01-20-93 (05:13)πFrom: GREG VIGNEAULT Number: 3196 [140] PascalπSubj: CRITICAL ERROR HANDLER Status: Publicπ------------------------------------------------------------------------------πDK> Can anyone PLEASE give me information on how to write a criticalπ > error handler.ππ Below is a quick'n-dirty critical error handler, written withoutπ any Asm (so is usable from TP v4.0+). To test it, put a write-π protected diskette in drive A:, then run the program. It shouldπ report error #19 (13 hex, disk write-protected).ππ It'll need to be modified & trimmed to your purpose. You mightπ code your handler to simply ignore errors, then let your mainπ program take appropriate action, depending on the error, etc.ππ DOS functions $00..$0C, $30, and $59 should be safe calls from theπ handler. Function $59 will return the extended error informationπ code that you'll need to check (eg. #32 = share violation), as wellπ as other data - which you can read up on, in a Dos reference text.ππ I've used one byte of the DOS intra-process communication area (atπ $40:$F0) to return the value needed to tell Dos what to do aboutπ the error, rather than juggle registers. This should be okay.ππ This code is cramped, to fit into a single message ...ππ{*******************************************************************}π PROGRAM Example; { Critical Error Handler }π USES Dos, { import MsDos, GetIntVec, SetIntVec, Registers }π Crt; { import CheckBreak }π VAR OldISR : POINTER; { to save original ISR ptr }π Reg : Registers; { to access CPU registers }π errNumber : WORD; { extended error code }π errClass, { error class }π errAction, { recommended action }π errLocus : BYTE; { error locus }π FileName : String[13]; { for ASCIIZ file name }π{-------------------------------------------------------------------}π PROCEDURE cErrorISR( AX,BX,CX,DX,SI,DI,DS,ES,BP : WORD); Interrupt;π BEGIN { This is it! ... }π InLine($FB); { STI (allow interrupts) }π Reg.AX := $3000; MsDos(Reg); { fn: get Dos version }π IF (Reg.AH < 3) THEN Reg.AL := 3 { if less than Dos 3+ :FAIL }π ELSE BEGIN { else take a closer look.. }π Reg.AH := $59; Reg.BX := 0; { fn: get extended info }π MsDos( Reg ); { call Dos }π errNumber := Reg.AX; { set|clear error number }π errClass := Reg.BH; errAction := Reg.BL; errLocus := Reg.CH;π WriteLn; Write( 'Critical error (#', errNumber, ') ' );π REPEAT WriteLn; { loop for user response }π Write( 'Abort, Retry, Ignore, Fail (A|R|I|F) ? ',#7);π Reg.AH := 1; MsDos(Reg); { get user input, via Dos }π UNTIL UpCase(CHR(Reg.AL)) IN ['A','R','I','F'];π CASE CHR(Reg.AL) OF { ... depending on input }π 'i','I' : Reg.AL := 0; { = ignore error }π 'r','R' : Reg.AL := 1; { = retry the action }π 'a','A' : Reg.AL := 2; { = abort }π 'f','F' : Reg.AL := 3; { = fail }π END; {case}π END; {if Reg.AH}π Mem[$40:$F0] := Reg.AL; { to tell Dos what to think }π InLine( $8B/$E5/ { mov sp,bp }π $5D/$07/$1F/$5F/$5E/ { pop bp,es,ds,di,si }π $5A/$59/$5B/$58/ { pop dx,cx,bx,ax }π $06/ { push es }π $2B/$C0/ { sub ax,ax }π $8E/$C0/ { mov es,ax }π $26/$A0/$F0/$04/ { mov al,es:[4F0h] }π $07/ { pop es }π $CF); { iret }π END {cErrorISR};π{-------------------------------------------------------------------}π BEGIN { the main program... }π CheckBreak := FALSE; { don't allow Ctrl-Break! }π errNumber := 0; { clear the error code }π GetIntVec( $24, OldISR ); { save current ISR vector }π SetIntVec( $24, @cErrorISR ); { set our ISR }π {===========================================================}π { insert your test code here ... }π FileName := 'A:TEST.TXT' + CHR(0); { ASCIIZ file name }π Reg.DS := SEG( FileName ); { file name segment }π Reg.DX := OFS( FileName[1] ); { file name offset }π Reg.CX := 0; { normal attribute }π Reg.AH := $3C; { fn: create file }π MsDos( Reg ); { via Dos }π {===========================================================}π IF (errNumber <> 0) THEN BEGINπ Write(#13#10#10,'For error #',errNumber,', user requested ');π CASE Mem[$40:$F0] OFπ 0 : WriteLn('IGNORE'); { just your imagination }π 1 : WriteLn('RETRY'); { ... endless futility ? }π 2 : WriteLn('ABORT'); { DOS won't come back here! }π 3 : WriteLn('FAIL'); { call technical support }π END; {case}π END; {if errNumber<>0}π SetIntVec( $24, OldISR ); { must restore original ISR }π END.π{*******************************************************************}ππ Greg_ππ Jan.20.1993.Toronto.Canada. greg.vigneault@bville.gts.orgπ---π * Baudeville BBS Toronto CANADA 416-283-0114 2200+ confsπ * PostLink(tm) v1.04 BAUDEVILLE (#1412) : RelayNet(tm)π 7 05-31-9308:08ALL GAYLE DAVIS Int29 Char Capture IMPORT 22 ==============================================================================π BBS: -=- Edge of the Century -=-π To: PERCY WONG Date: 03-22-93 (10:19)πFrom: GAYLE DAVIS Number: 4475 [140] PascalπSubj: Capturing Dos Output Status: Publicπ------------------------------------------------------------------------------πPW>-> PW> EXEC(GETENV(COMSPEC),' \C DIR'); { or whatever it is }πPW>-> >can i then capture each line (or even one line) of the Dir output toππPercy or Kerry ??,ππAn elegant way of accomplishing your goal is to grap INT29. This is anπUNDOCUMENTED DOS function, however, it's really simple to use. DOS usesπthis to write EVERYTHING to the screen. The problem is that there is a LOTπof data output when screen writing takes place. If you try to capture toπmuch you will need LOTS of memory. However, short output like your tryingπto get is OK.ππHere is some sample code that will let you capture output :πππ{$A+,B-,D+,E+,F-,G+,I+,L+,N-,O-,P-,Q-,R-,S+,T-,V-,X+,Y+}π{$M 4096,0,400000}ππUses DOS,Crt;ππTypeπ ISRRegisters =π recordπ case Byte ofπ 1 : (BP, ES, DS, DI, SI, DX, CX, BX, AX, IP, CS, Flags : Word);π 2 : (j1,j2,j3,j4,j5 : Word; DL, DH, CL, CH, BL, BH, AL, AH : Byte);π end;ππCONSTππ OrigInt29 : Pointer = nil; {Old int 29 vector}ππVarπ grab : Array[1..32768] Of Char; { this MAY NOT be enough !!! }π idx : LongInt; { if output EXCEEDS this, might }π { lock up machine, so be careful }π S : String;π I : LongInt;ππ{ Here is the MAGIC }πprocedure Int29(BP : Word); interrupt;ππvarπ Regs : ISRRegisters absolute BP;ππbeginπππ Grab[Idx] := CHAR(Regs.AL);π Inc(idx);ππ { WILL LOOSE OUTPUT, BUT BETTER THAN LOCKING MACHINE !!}π If Idx > SizeOf(Grab) THEN Idx := 1;ππ ASMπ PopFπ call OrigInt29π END;ππend;ππBEGINππ GetIntVec($29, OrigInt29);π SetIntVec($29, @Int29);πππ Clrscr;π Idx := 1;ππ {Shell to DOS and run your program}ππ SwapVectors;π Exec(GetEnv('COMSPEC'), '/c '+ YOURPROGRAM);π SwapVectors;ππ { GRAB now contains ALL of our output }ππ FOR I := 1 TO Idx DOπ BEGINπ If Grab[i] = #10 Then BEGINπ WriteLn(S);π S := ''π END ELSE If Grab[i] <> #13 THEN S := S + Grab[i];ππ END;ππ { ABSOLUTELY MUST BE DONE !! }π if OrigInt29 <> nil then SetIntVec($29, OrigInt29);πππUtiExprt: To be continued in next message ...π---π * T.I.F.S.D.B.(from MD,USA 301-990-6362)π * PostLink(tm) v1.05 TIFSDBU (#1258) : RelayNet(TM)π 8 08-17-9308:40ALL SWAG SUPPORT TEAM Hooking an interrupt IMPORT 27 «F PROGRAM CatchInt;ππUSESπ Crt,Dos,Printer;ππ{This program illustrates how you can modify anπ interrupt service routine to perform specialπ services for you.}ππ VARπ OldInt,OldExitProc: pointer;π IntCount: array[0..255] of byte;ππ PROCEDURE GoOldInt(OldIntVector: pointer);π INLINE (π $5B/ {POP BX - Get Segment}π $58/ {POP AX - Get Offset}π $89/ {MOV SP,BP}π $EC/π $5D/ {POP BP}π $07/ {POP ES}π $1F/ {POP DS}π $5F/ {POP DI}π $5E/ {POP SI}π $5A/ {POP DX}π $59/ {POP CX}π $87/ {XCHG SP,BP}π $EC/π $87/ {XCHG [BP],BX}π $5E/π $00/π $87/ {XCHG [BP+2],AX}π $46/π $02/π $87/ {XCHG SP,BP}π $EC/π $CB); {RETF}πππ {$F+}ππ PROCEDURE NewExitProc;ππ VAR I: byte;π VAR A: char;ππ FUNCTION Intr21Desc(IntNbr: byte): string;ππ VARπ St : string[30];ππ BEGINπ CASE IntNbr ofπ $25: St := 'Set Interrupt Vector';π $36: St := 'Get Disk Free Space';π $3C: St := 'Create File with Handle';π $3E: St := 'Close FILE';π $40: St := 'WriteFile or Device';π $41: St := 'Delete FILE';π $44: St := 'IOCTL';π $3D: St := 'Open File with Handle';π $3F: St := 'Read File or Device';π $42: St := 'Move File pointer';π ELSEπ St := 'Unknown DOS Service'π END;π Intr21Desc := St;π END;πππ FUNCTION DecToHex(Deci: byte): string;ππ CONSTπ ConvStr: string[16] = '0123456789ABCDEF';π BEGINπ DecToHex := ConvStr[Deci div 16 + 1] +π ConvStr[Deci mod 16 + 1]π END;πππ BEGINπ ClrScr;π ExitProc := OldExitProc;π SetIntVec($21,OldInt);π WriteLn('Int # Description');π WriteLn(' # Times');π WriteLn;π FOR I:= 0 TO 255 DOπ BEGINπ IF IntCount[I] <> 0 THENπ BEGINπ Write(DecToHex(I),'H');π Write(' ',IntCount[I]:3);π GotoXY(11,WhereY);π WriteLn(Intr21Desc(I))π ENDπ ENDπ END;πππ PROCEDURE NewInt(AX,BX,CX,DX,SI,π DI,SD,ES,BP: Word); INTERRUPT;ππ VAR AH: byte;ππ BEGINπ Sound(1220);Delay(10);NoSound;π AH := Hi(AX);π IntCount[AH] := IntCount[AH]+1;π GoOldInt(OldInt)π END;π {$F-}ππ{************ Main Program *****************}ππ VAR I: byte;π F: text;π TestStr: string[40];ππ BEGINππ ClrScr;ππ{Install new Exit PROCEDURE}ππ OldExitProc := ExitProc;π ExitProc := @NewExitProc;ππ{Install new Interrupt Vector}ππ GetIntVec($21, OldInt);π SetIntVec($21, @NewInt);ππ{******** Testing Section ***********}ππ WriteLn('Starting Testing');Delay(1000);ππ FillChar(IntCount,SizeOf(IntCount),#0);ππ FOR I:= 0 TO 255 DOπ WriteLn('Testing 1'); {WriteLn's to screens}π {do not use the 21H }π {Interrupt }ππ Write('TYPE anything TO test keyboard: ');π ReadLn(TestStr);ππ Writeln('Disk Size ',π DiskSize(3)); {Uses Service 36H}πππ Assign (F,'TestFile');π Rewrite(f); {Uses Service 3CH,44H}ππ FOR I:=0 TO 255 DOπ WriteLn(F,'This is only A test'); {Service 40H}π WriteLn(F,'This is A test too');π WriteLn(f,'Last test');ππ Close(f); {Uses Service 3EH,40H}ππ Assign(F,'TestFile');π Append(f); {Uses Service 3DH,3FH,42H,44H}π Close(F); {Uses Service 3EH,40H}ππ Assign(F,'TestFile');π Erase(f) {Uses Service 41H}π END.π 9 08-17-9308:44ALL CHRIS PRIEDE Trapping Int21 IMPORT 22 «F ===========================================================================π BBS: Canada Remote SystemsπDate: 07-15-93 (18:15) Number: 26295πFrom: CHRIS PRIEDE Refer#: 26227π To: PIERRE DARMON Recvd: NO πSubj: DOS interrupt handler Conf: (552) R-TPπ---------------------------------------------------------------------------πPD>What additional steps need to be taken for $21? I even tried to removeπPD>the clicking part, which boils down to installing a new handler that justπPD>calls the old one. Still no go. What's wrong?ππPD>My ultimate goal is to trap file opens (function 3Dh), check the SHAREingπPD>mode used (in AL), modify it if necessary, and execute the old handler.πPD>Doesn't sound like a very complicated thing to do but ... I am stuck.ππ Your handler is changing some registers or suffering from someπregisters being changed by INT 21. DOS EXEC service trashes everything,πincluding SS:SP, for example. In my opinion, one can't write a stableπINT 21 handler in Pascal or any other HLL. HLL interrupt handlers areπusable to certain extent, but this is too low level.ππ It can be done in BASM, though. We will declare interrupt handler asπsimple procedure with no arguments to avoid entry/exit code TP generatesπfor interrupt handlers. Our handler will force all files to be opened inπDeny Write mode (modify for your needs).πππconstπ shCompatibility = $00;π shDenyAll = $10;π shDenyWrite = $20;π shDenyRead = $30;π shDenyNone = $40;ππprocedure NewInt21; assembler;πasmπ cmp ah, 3Dh {open file?}π je @CheckModeALπ cmp ah, 6Ch {DOS 4.0+ extended open?}π je @CheckModeBL {extended takes mode in BX}π jmp @Chainππ@CheckModeAL:π and al, 10001111b {clear sharing mode bits}π or al, shDenyWrite {set to our mode}π jmp @Chainππ@CheckModeBL:π and bl, 10001111bπ or bl, shDenyWriteπ jmp @Chainππ@I21:π DD 0 {temp. var. for old vector -- must be in code seg.}ππ@Chain:π push dsπ push axπ mov ax, SEG @Dataπ mov ds, axπ mov ax, WORD PTR OldInt21π mov WORD PTR cs:[offset @I21], axπ mov ax, WORD PTR OldInt21 +2π mov WORD PTR cs:[offset @I21 +2], axπ pop axπ pop dsπ jmp DWORD PTR cs:[offset @I21]πend;πππ To try this save old vector in a global variable named OldInt21 andπinstall this handler as usual. It also traps function 6Ch, DOS 4.0+πextended open/create. Very few programs use it, but why not...π---π * Faster-Than-Light (FTL) ■ Atlanta, GA ■ 404-292-8761/299-3930π * PostLink(tm) v1.06 FTL (#93) : RelayNet (tm)π 10 08-27-9320:26ALL JONATHAN WRITE Changing the Int08 Rate IMPORT 18 «F {πJONATHAN WRIGHTππ> A/D (analog to digital conversion). Somehow I need to use the PCπ> clock/timer to call my A/D sampling interrupt at various rates fromπ> several hundred Hz to several thousand Hz.ππ> Hook interrupt 1Ch and point it to your interrupt handler. Useπ> a counter in this procedure to count the number of interrupts orππThis will not work correctly. Using interrupt 1Ch as it is normally set up,πyour interrupt routine will only be called 18 times a second (18.2, actually),πso you could get a maximum of 18.2 Hz. If you wait until a counter in thisπinterrupt (incremented by 1 each time) reaches 1820, it will take 10 seconds!πIt WON'T be 100 Hz.ππIn order to hook the timer interrupt at a rate above 18.2 Hz, you'll need toπrevector int 08h (which calls int 1Ch anyway). You'll have to set up a counterπin int 08h which makes sure that the ORIGINAL int 08h routine is still calledπ18.2 times a second. The value for this counter will vary, depending on howπfast you set timer channel 0. The system clock has a maximum resolution ofπabout 1.19318 Mhz and IRQ0 is normally called 1193180/65536 times per second.ππHere's some code for changing the clock rate (sorry but it's ASM):π}π;*********************π; called by SetClockRate (which is Pascal callable)ππClkRate PROC NEARππ push axπ mov al,36hπ out 43h,alπ pop axπ out 40h,al xchg ah,alπ out 40h,alπ retπClkRate ENDPππ;******************π; call this routine from TP as SetClockRate (Hz : WORD);πSetClockRate PROC FARππRate EQU word ptr [bp+06]π push bpπ mov bp,spπ cmp rate,0π je SCR01ππ mov ax,65535π xor dx,dxπ mov bx,rateπ div bxπ jmp SCR02ππSCR01:π xor ax,axππSCR02:π call ClkRateππ mov sp,bpπ pop bpπ ret 2ππSetClockRate ENDPππI pulled these procedures from some OLD code which I may have inadvertenlyπscrewed up over time, but it looks o.k.π Actually revectoring int 08h is a bit more complex - you MUST make sure theπold it 08 is called appropriately because it controls a number of systemπfunctions and your PC WILL lock up if it's not called. I recommend finding aπbook to help with that part.π 11 08-27-9320:39ALL BRYCE OSTENSON Handling Ctrl-Break IMPORT 10 «F {πBRYCE OSTENSONππ> I am looking for a way to diable the use of the control break and controlπ> alt delete features.ππBTW: Simple concept... Here's how it works - When the program begins,πSavedInt23 is assigned to the original C-Break interrupt... When theπSetCtrlBreak procedure is called with Status equaling false, the C-Breakπinterrupt is assigned to a CBreakHandler which has no substance... Thusπwhen C-Break is called it does nothing. When SetCtrlBreak is calledπwith Status equaling false, Interrupt 23h is assigned to the defaultπC-Break handler.π}ππUNIT TBUtil;ππINTERFACEππUsesπ Dos;ππVarπ SavedInt23 : Pointer;π CBreak : Boolean;ππProcedure SetCtrlBreak(Status : Boolean);πFunction GetCtrlBreak : Boolean;ππIMPLEMENTATIONππProcedure CBreakHandler; INTERRUPT;πBeginπEnd;ππProcedure SetCtrlBreak(Status : Boolean);πBeginπ If Status thenπ SetIntVec($23, SavedInt23);π Elseπ SetIntVec($23, @CBreakHandler);π CBreak := Status;πEnd;ππFunction GetCtrlBreak : Boolean;πBeginπ GetCtrlBreak := CBreak;πEnd;ππBeginπ CBreak := True;π GetIntVec($23, SavedInt23); { Save the Ctrl-Break handler. }πEnd.ππ