home *** CD-ROM | disk | FTP | other *** search
- *** C:\OLD\RTL\COMMON\OBJECTS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\COMMON\OBJECTS.PAS Thu Mar 04 07:01:00 1993
- *** 1579-1585 ****
- PUSH DI
- CALL ChangeListSize
- LES DI,Self
- ! OR AX,AX
- JNZ @@2
- MOV DX,stInitError
- CALL DoStreamError
- --- 1579-1585 ----
- PUSH DI
- CALL ChangeListSize
- LES DI,Self
- ! OR AL,AL
- JNZ @@2
- MOV DX,stInitError
- CALL DoStreamError
-
- *** 1611-1616 ****
- --- 1611-1617 ----
- begin
- AItems := MemAlloc(ALimit * SizeOf(Word));
- if AItems = nil then Exit;
- + FillChar(AItems^, ALimit * SizeOf(Word), 0);
- if (SegCount <> 0) and (SegList <> nil) then
- if SegCount > ALimit then
- Move(SegList^, AItems^, ALimit * SizeOf(Word))
-
- *** 1623-1629 ****
- Term := SegCount - 1;
- while Dif <= Term do
- begin
- ! FreeMem(Ptr(SegList^[Dif], 0), BlockSize);
- Inc(Dif);
- end;
- end
- --- 1624-1631 ----
- Term := SegCount - 1;
- while Dif <= Term do
- begin
- ! if SegList^[Dif] <> 0 then
- ! FreeMem(Ptr(SegList^[Dif], 0), BlockSize);
- Inc(Dif);
- end;
- end
-
- *** 1634-1649 ****
- while Dif <= Term do
- begin
- NewBlock := MemAllocSeg(BlockSize);
- ! if NewBlock = nil then Exit
- else AItems^[Dif] := PtrRec(NewBlock).Seg;
- Inc(Dif);
- end;
- end;
- if SegCount <> 0 then FreeMem(SegList, SegCount * SizeOf(Word));
- SegList := AItems;
- SegCount := ALimit;
- ! end;
- ! ChangeListSize := True;
- end;
-
- function TMemoryStream.GetPos: Longint; assembler;
- --- 1636-1652 ----
- while Dif <= Term do
- begin
- NewBlock := MemAllocSeg(BlockSize);
- ! if NewBlock = nil then Break
- else AItems^[Dif] := PtrRec(NewBlock).Seg;
- Inc(Dif);
- end;
- + if Dif = ALimit then
- + ChangeListSize := True;
- end;
- if SegCount <> 0 then FreeMem(SegList, SegCount * SizeOf(Word));
- SegList := AItems;
- SegCount := ALimit;
- ! end else ChangeListSize := True;
- end;
-
- function TMemoryStream.GetPos: Longint; assembler;
-
- *** 1752-1758 ****
- PUSH ES
- PUSH DI
- CALL ChangeListSize
- ! OR AX,AX
- JNZ @@1
- MOV DX,stError
- CALL DoStreamError
- --- 1755-1761 ----
- PUSH ES
- PUSH DI
- CALL ChangeListSize
- ! OR AL,AL
- JNZ @@1
- MOV DX,stError
- CALL DoStreamError
-
- *** 1790-1796 ****
- POP DI
- POP ES
- POP BX
- ! OR AX,AX
- JNZ @@4
- @@1: MOV DX,stWriteError
- CALL DoStreamError
- --- 1793-1799 ----
- POP DI
- POP ES
- POP BX
- ! OR AL,AL
- JNZ @@4
- @@1: MOV DX,stWriteError
- CALL DoStreamError
-
- *** C:\OLD\RTL\OWL\ODIALOGS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\OWL\ODIALOGS.PAS Thu Mar 04 07:01:00 1993
- *** 1361-1367 ****
-
- if (Validator <> nil) and (GetNumLines <= 1) then
- begin
- ! GetText(Sz, TextLen);
- S := StrPas(Sz);
-
- if ReportError then
- --- 1361-1371 ----
-
- if (Validator <> nil) and (GetNumLines <= 1) then
- begin
- ! if TextLen > High(Sz) then
- ! GetText(Sz, High(Sz))
- ! else
- ! GetText(Sz, TextLen);
- !
- S := StrPas(Sz);
-
- if ReportError then
-
- *** 1635-1653 ****
- var
- S : string;
- Sz, OldSz : array [0..255] of Char;
- StartPos, EndPos: Integer;
- WasAppending: Boolean;
- begin
- if (Validator <> nil) and (GetNumLines <= 1) and
- (Msg.wParam <> vk_Back) then
- begin
- ! GetText(OldSz, TextLen);
- GetSelection(StartPos, EndPos);
- WasAppending := EndPos = StrLen(OldSz);
-
- DefWndProc(Msg); { Process the new char ... }
-
- ! GetText(Sz, TextLen);
- S := StrPas(Sz); { Validator expects a Pascal string }
-
- { Run the result of the edit through the validator. If incorrect,
- --- 1639-1660 ----
- var
- S : string;
- Sz, OldSz : array [0..255] of Char;
- + Len : Integer;
- StartPos, EndPos: Integer;
- WasAppending: Boolean;
- begin
- if (Validator <> nil) and (GetNumLines <= 1) and
- (Msg.wParam <> vk_Back) then
- begin
- ! Len := TextLen;
- ! if Len > High(OldSz) then Len := High(OldSz);
- ! GetText(OldSz, Len);
- GetSelection(StartPos, EndPos);
- WasAppending := EndPos = StrLen(OldSz);
-
- DefWndProc(Msg); { Process the new char ... }
-
- ! GetText(Sz, Len);
- S := StrPas(Sz); { Validator expects a Pascal string }
-
- { Run the result of the edit through the validator. If incorrect,
-
- *** C:\OLD\RTL\SYS\DAPP.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\SYS\DAPP.ASM Thu Mar 04 07:01:00 1993
- *** 23-28 ****
- --- 23-32 ----
- EXTRN ExitCode:WORD,ErrorAddr:DWORD,Test8086:BYTE
- EXTRN SaveInt21:DWORD
-
- + ; Local workspace
- +
- + SaveInt10 DD ?
- +
- DATA ENDS
-
- ; Run-time manager externals
-
- *** 41-47 ****
-
- ; Publics
-
- ! PUBLIC InitTurbo
-
- ; CS-based variables for Ctrl-Break handling
-
- --- 45-51 ----
-
- ; Publics
-
- ! PUBLIC InitTurbo,ExceptHalt
-
- ; CS-based variables for Ctrl-Break handling
-
-
- *** 86-91 ****
- --- 90-100 ----
- ADD DI,4
- POP CX
- LOOP @@1
- + MOV AX,dpmiGetExcept ;Save exception 10H vector
- + MOV BL,10H
- + INT DPMI
- + MOV SaveInt10.ofs,DX
- + MOV SaveInt10.seg,CX
- MOV AX,CS ;Get code segment alias
- ADD AX,__AHIncr
- MOV ES,AX
-
- *** 186-191 ****
- --- 195-205 ----
- PUSH AX
- PUSH CS
- CALL CloseText
- + MOV AX,dpmiSetExcept ;Restore exception 10H vector
- + MOV BL,10H
- + MOV DX,SaveInt10.ofs
- + MOV CX,SaveInt10.seg
- + INT DPMI
- MOV DI,OFFSET SaveInt00 ;Restore interrupt vectors
- MOV SI,OFFSET SaveIntTab
- MOV CX,SaveIntCnt
-
- *** C:\OLD\RTL\SYS\F87H.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\SYS\F87H.ASM Thu Mar 04 07:01:00 1993
- *** 34-39 ****
- --- 34-40 ----
- ; Externals
-
- EXTRN PrefixSeg:WORD,Test8087:BYTE,SaveInt02:DWORD
- + EXTRN ExitCode:WORD,ErrorAddr:DWORD
-
- ; Local workspace
-
-
- *** 56-61 ****
- --- 57-65 ----
- ; Externals
-
- EXTRN HaltTurbo:NEAR,HaltError:NEAR,Terminate:NEAR
- + IF DPMIVersion
- + EXTRN ExceptHalt:NEAR
- + ENDIF
-
- ; Publics
-
-
- *** 72-78 ****
-
- ; Turn off emulation for 8087 presence test
-
- ! NOEMUL
-
- ; Check if 8087 is present
- ; Out AL = 8087 flag (0/1/2/3)
- --- 76-82 ----
-
- ; Turn off emulation for 8087 presence test
-
- ! NOEMUL
-
- ; Check if 8087 is present
- ; Out AL = 8087 flag (0/1/2/3)
-
- *** 106-114 ****
- ; presence, instruct the processor to store its control word in
- ; memory, and then check if it actually did it.
-
- ! @@3: XOR AX,AX ;Clear 80287 BUSY latch
- ! OUT 0F0H,AL
- ! FNINIT ;Initialize 80x87
- MOV [BX],AX ;Clear status word
- FNSTCW [BX] ;Store status word
- MOV CX,20 ;Wait for a while
- --- 110-122 ----
- ; presence, instruct the processor to store its control word in
- ; memory, and then check if it actually did it.
-
- ! @@3: XOR AX,AX
- ! PUSH SP ;Check 8088/8086
- ! POP DX
- ! CMP DX,SP ;Not equal on 8088/8086
- ! JNE @@3a
- ! OUT 0F0H,AL ;Clear 80287 BUSY latch
- ! @@3a: FNINIT ;Initialize 80x87
- MOV [BX],AX ;Clear status word
- FNSTCW [BX] ;Store status word
- MOV CX,20 ;Wait for a while
-
- *** 150-156 ****
-
- ; Turn emulation back on
-
- ! EMUL
-
- ; Initialize 8087 emulator
- ; In SI = Emulator entry offset
- --- 158-164 ----
-
- ; Turn emulation back on
-
- ! EMUL
-
- ; Initialize 8087 emulator
- ; In SI = Emulator entry offset
-
- *** 177-182 ****
- --- 185-195 ----
- INT DOS
- POP DS
- IF DPMIVersion
- + MOV AX,dpmiSetExcept ;Install FP exception handler
- + MOV BL,10H
- + MOV DX,OFFSET Int10Handler
- + MOV CX,CS
- + INT DPMI
- MOV AX,CS ;Get code segment alias
- ADD AX,__AHIncr
- MOV ES,AX
-
- *** 218-248 ****
- JNE @@1 ;Yes, @@1
- FSTENV EnvBuffer ;Store environment
- JMP SHORT @@2
- ! NOEMUL ;Can't emulate no-wait opcode
- @@1: FNSTENV EnvBuffer ;No wait, store environment
- FWAIT ;Wait for it
- ! EMUL ;Turn emulation back on
- @@2: MOV AL,CtrlWord.b0 ;Unmasked exceptions to AL
- NOT AL
- AND AL,StatWord.b0
- ! JS Exception ;IR=1 if 8087 caused interrupt
- ! POP DS ;Restore registers
- POP AX
- !
- ! ; Jump to saved INT 2 handler
- !
- ! DB 0EAH ;JMP FAR
- ! JumpInt02 DD ?
-
- ! ; 8087 exception handler
-
- ! Exception:
-
- - STI ;Enable interrupts
- - TEST AL,3FH-mDE ;Anything but denormal exception
- - JE FixDenormal ;is an error
- FINIT ;Initialize 8087
- FLDCW CWDefault
- POP CX ;Remove saved registers
- POP CX
- POP CX ;Get interrupt return address
- --- 231-259 ----
- JNE @@1 ;Yes, @@1
- FSTENV EnvBuffer ;Store environment
- JMP SHORT @@2
- ! NOEMUL ;Can't emulate no-wait opcode
- @@1: FNSTENV EnvBuffer ;No wait, store environment
- FWAIT ;Wait for it
- ! EMUL ;Turn emulation back on
- @@2: MOV AL,CtrlWord.b0 ;Unmasked exceptions to AL
- NOT AL
- AND AL,StatWord.b0
- ! JNS Int02Chain ;IR=1 if 8087 caused interrupt
- ! STI ;Enable interrupts
- ! TEST AL,3FH-mDE ;Anything but denormal exception
- ! JNE Int02Error ;is an error
- ! CALL FixDenormal
- ! POP DS
- POP AX
- ! IRET
-
- ! ; Terminate application
-
- ! Int02Error:
-
- FINIT ;Initialize 8087
- FLDCW CWDefault
- + CALL GetErrorCode
- POP CX ;Remove saved registers
- POP CX
- POP CX ;Get interrupt return address
-
- *** 262-285 ****
- MOV CX,Instruction.ofs
- AND CX,0FH
- ENDIF
- ! @@1: TEST AL,mIE ;Convert exception mask to
- ! JNE @@2 ;run-time error number
- ! MOV DX,200
- TEST AL,mZE
- JNE @@3
- ! MOV DX,205
- TEST AL,mOE
- JNE @@3
- ! MOV DX,206
- TEST AL,mUE
- JNE @@3
- ! @@2: MOV DX,207
- ! @@3: XCHG AX,DX ;Error code to AX
- ! JMP Terminate ;Run-time error
-
- ; Denormal exceptions never occur with the emulator
-
- ! NOEMUL
-
- ; Retry subroutine
-
- --- 273-357 ----
- MOV CX,Instruction.ofs
- AND CX,0FH
- ENDIF
- ! @@1: JMP Terminate
- !
- ! ; Chain to old INT 02H handler
- !
- ! Int02Chain:
- !
- ! POP DS ;Restore registers
- ! POP AX
- !
- ! ; Jump to saved INT 2 handler
- !
- ! DB 0EAH ;JMP FAR
- ! JumpInt02 DD ?
- !
- ! IF DPMIVersion
- !
- ! NOEMUL
- !
- ! ; Exception 10H handler (Borland DPMI server)
- !
- ! Int10Handler:
- !
- ! PUSH BP
- ! MOV BP,SP
- ! PUSH AX
- ! PUSH DS
- ! MOV AX,SEG DATA
- ! MOV DS,AX
- ! FNSTENV EnvBuffer
- ! FWAIT
- ! MOV AL,CtrlWord.b0 ;Unmasked exceptions to AL
- ! NOT AL
- ! AND AL,StatWord.b0
- ! TEST AL,3FH-mDE ;Anything but denormal exception
- ! JE @@1 ;is an error
- ! FINIT ;Initialize 8087
- ! FLDCW CWDefault
- ! CALL GetErrorCode
- ! MOV ExitCode,AX
- ! MOV AX,Instruction.ofs
- ! MOV ErrorAddr.ofs,AX
- ! MOV AX,Instruction.seg
- ! MOV ErrorAddr.seg,AX
- ! MOV [BP+8].ofs,OFFSET ExceptHalt
- ! MOV [BP+8].seg,CS
- ! JMP SHORT @@2
- ! @@1: CALL FixDenormal
- ! @@2: POP DS
- ! POP AX
- ! POP BP
- ! RETF
- !
- ! EMUL
- !
- ! ENDIF
- !
- ! ; Convert exception mask to error code
- !
- ! GetErrorCode:
- !
- ! TEST AL,mIE
- ! JNE @@2
- ! MOV AH,200
- TEST AL,mZE
- JNE @@3
- ! MOV AH,205
- TEST AL,mOE
- JNE @@3
- ! MOV AH,206
- TEST AL,mUE
- JNE @@3
- ! @@2: MOV AH,207
- ! @@3: MOV AL,AH
- ! XOR AH,AH
- ! RET
-
- ; Denormal exceptions never occur with the emulator
-
- ! NOEMUL
-
- ; Retry subroutine
-
-
- *** 370-378 ****
- POP ES
- ENDIF
- POP BX ;Restore and return
- ! POP DS
- ! POP AX
- ! IRET
-
- ; Examine ST and normalize if required
-
- --- 442-448 ----
- POP ES
- ENDIF
- POP BX ;Restore and return
- ! RET
-
- ; Examine ST and normalize if required
-
-
- *** 399-405 ****
-
- ; Turn emulation back on
-
- ! EMUL
-
- ; Convert Real to Extended
-
- --- 469-475 ----
-
- ; Turn emulation back on
-
- ! EMUL
-
- ; Convert Real to Extended
-
-
- *** C:\OLD\RTL\SYS\LONG.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\SYS\LONG.ASM Thu Mar 04 07:01:00 1993
- *** 166-173 ****
- CMP Test8086,2
- JB @@1
- .386
- ! SHRD AX,DX,CL
- ! SHR DX,CL
- RETF
- .8086
- @@1: AND CX,1FH
- --- 166-176 ----
- CMP Test8086,2
- JB @@1
- .386
- ! SHL EDX,16
- ! MOV DX,AX
- ! SHR EDX,CL
- ! MOV AX,DX
- ! SHR EDX,16
- RETF
- .8086
- @@1: AND CX,1FH
-
- *** 187-194 ****
- CMP Test8086,2
- JB @@1
- .386
- ! SHLD DX,AX,CL
- ! SHL AX,CL
- RETF
- .8086
- @@1: AND CX,1FH
- --- 190-200 ----
- CMP Test8086,2
- JB @@1
- .386
- ! SHL EDX,16
- ! MOV DX,AX
- ! SHL EDX,CL
- ! MOV AX,DX
- ! SHR EDX,16
- RETF
- .8086
- @@1: AND CX,1FH
-
- *** C:\OLD\RTL\SYS\LOVF.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\SYS\LOVF.ASM Thu Mar 04 07:01:00 1993
- *** 76-81 ****
- --- 76-84 ----
- MUL CX
- ADD DX,DI
- JC @@5
- + MOV CX,AX
- + OR CX,DX
- + JE @@6
- OR SI,SI
- JNS @@4
- NEG AX
-
- *** 83-89 ****
- NEG DX
- @@4: XOR SI,DX
- JS @@5
- ! RETF
- @@5: JMP Overflow
-
- CODE ENDS
- --- 86-92 ----
- NEG DX
- @@4: XOR SI,DX
- JS @@5
- ! @@6: RETF
- @@5: JMP Overflow
-
- CODE ENDS
-
- *** C:\OLD\RTL\SYS\WLIB.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\SYS\WLIB.ASM Thu Mar 04 07:01:00 1993
- *** 68-74 ****
- MOV SelectorInc,__AHIncr
- MOV ExitCode,1 ;Default exit code is 1
- EXIT
- ! @@3: MOV BP,SP ;Remove stack frame
- POP BP
- DEC BP
- POP CX ;Remove return address
- --- 68-74 ----
- MOV SelectorInc,__AHIncr
- MOV ExitCode,1 ;Default exit code is 1
- EXIT
- ! @@3: MOV SP,BP ;Remove stack frame
- POP BP
- DEC BP
- POP CX ;Remove return address
-
- *** C:\OLD\RTL\TV\DIALOGS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\DIALOGS.PAS Thu Mar 04 07:01:00 1993
- *** 1036-1048 ****
- end;
-
- function TInputLine.Valid(Command: Word): Boolean;
- begin
- Valid := inherited Valid(Command);
- if (Validator <> nil) and (State and sfDisabled = 0) then
- if Command = cmValid then
- Valid := Validator^.Status = vsOk
- else if Command <> cmCancel then
- ! if not Validator^.Valid(Data^) then
- begin
- Select;
- Valid := False;
- --- 1036-1061 ----
- end;
-
- function TInputLine.Valid(Command: Word): Boolean;
- +
- + function AppendError(Validator: PValidator): Boolean;
- + begin
- + AppendError := False;
- + with Validator^ do
- + if (Options and voOnAppend <> 0) and (CurPos <> Length(Data^))
- + and not IsValidInput(Data^, True) then
- + begin
- + Error;
- + AppendError := True;
- + end;
- + end;
- +
- begin
- Valid := inherited Valid(Command);
- if (Validator <> nil) and (State and sfDisabled = 0) then
- if Command = cmValid then
- Valid := Validator^.Status = vsOk
- else if Command <> cmCancel then
- ! if AppendError(Validator) or not Validator^.Valid(Data^) then
- begin
- Select;
- Valid := False;
-
- *** C:\OLD\RTL\TV\HISTLIST.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\HISTLIST.PAS Thu Mar 04 07:01:00 1993
- *** 113-122 ****
- MOV DI,HistoryUsed
- LDS SI,Str
- MOV BL,[SI]
- - INC BL
- - INC BL
- - INC BL
- XOR BH,BH
- POP DS
- PUSH DS
- @@1: MOV AX,DI
- --- 113-122 ----
- MOV DI,HistoryUsed
- LDS SI,Str
- MOV BL,[SI]
- XOR BH,BH
- + INC BX
- + INC BX
- + INC BX
- POP DS
- PUSH DS
- @@1: MOV AX,DI
-
- *** C:\OLD\RTL\TV\OUTLINE.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\OUTLINE.PAS Thu Mar 04 07:01:00 1993
- *** 900-909 ****
- if Node <> nil then
- with Node^ do
- begin
- ! if ChildList <> nil then DisposeNode(ChildList);
- ! if Next <> nil then DisposeNode(Next);
- end;
- - Dispose(Node);
- end;
-
- procedure RegisterOutline;
- --- 900-910 ----
- if Node <> nil then
- with Node^ do
- begin
- ! DisposeNode(ChildList);
- ! DisposeNode(Next);
- ! DisposeStr(Text);
- ! Dispose(Node);
- end;
- end;
-
- procedure RegisterOutline;
-
- *** C:\OLD\RTL\TV\STDDLG.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\STDDLG.PAS Thu Mar 04 07:01:00 1993
- *** 944-950 ****
- function RelativePath(var S: PathStr): Boolean;
- begin
- S := LTrim(RTrim(S));
- ! RelativePath := not (S <> '') and ((S[1] = '\') or (S[2] = ':'));
- end;
-
- function NoWildChars(S: String): String; near; assembler;
- --- 944-950 ----
- function RelativePath(var S: PathStr): Boolean;
- begin
- S := LTrim(RTrim(S));
- ! RelativePath := not ((S <> '') and ((S[1] = '\') or (S[2] = ':')));
- end;
-
- function NoWildChars(S: String): String; near; assembler;
-
- *** C:\OLD\RTL\TV\SYSINT.ASM Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\SYSINT.ASM Thu Mar 04 07:01:00 1993
- *** 59-64 ****
- --- 59-65 ----
- dpmiAllocDesc EQU 0000H ;Allocate descriptor
- dpmiFreeDesc EQU 0001H ;Free descriptor
- dpmiSetSegBase EQU 0007H ;Set segment base address
- + dpmiSetSegSize EQU 0008H ;Set segment size
- dpmiGetRealInt EQU 0200H ;Get real mode interrupt vector
- dpmiSetRealInt EQU 0201H ;Set real mode interrupt vector
- dpmiGetProtInt EQU 0204H ;Get protected mode interrupt vector
-
- *** 216-221 ****
- --- 217-227 ----
- MOV CX,1
- INT DPMI
- MOV TempSelector,AX
- + MOV BX,AX
- + XOR CX,CX
- + MOV DX,0FFFFH
- + MOV AX,dpmiSetSegSize
- + INT DPMI
- MOV AX,CS
- ADD AX,SelectorInc
- MOV ES,AX
-
- *** C:\OLD\RTL\TV\VIEWS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\TV\VIEWS.PAS Thu Mar 04 07:01:00 1993
- *** 3769-3775 ****
- (State and sfSelected <> 0)) then
- begin
- WindowCommands := [cmNext, cmPrev];
- ! if Flags and wfGrow + wfMove <> 0 then
- WindowCommands := WindowCommands + [cmResize];
- if Flags and wfClose <> 0 then
- WindowCommands := WindowCommands + [cmClose];
- --- 3769-3775 ----
- (State and sfSelected <> 0)) then
- begin
- WindowCommands := [cmNext, cmPrev];
- ! if Flags and (wfGrow + wfMove) <> 0 then
- WindowCommands := WindowCommands + [cmResize];
- if Flags and wfClose <> 0 then
- WindowCommands := WindowCommands + [cmClose];
-
- *** C:\OLD\RTL\WIN\WINDOS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\WIN\WINDOS.PAS Thu Mar 04 07:01:00 1993
- *** 500-509 ****
- PUSH BP
- MOV BP,SP
- {$IFDEF ProtectedMode}
- ! LES DI,Regs+14
- {$ELSE}
- ! LES DI,Regs+12
- {$ENDIF}
- CLD
- STOSW
- XCHG AX,BX
- --- 500-510 ----
- PUSH BP
- MOV BP,SP
- {$IFDEF ProtectedMode}
- ! ADD BP,14
- {$ELSE}
- ! ADD BP,12
- {$ENDIF}
- + LES DI,Regs
- CLD
- STOSW
- XCHG AX,BX
-
- *** C:\OLD\RTL\WIN\WINPROCS.PAS Wed Oct 28 07:00:00 1992
- --- C:\NEW\RTL\WIN\WINPROCS.PAS Thu Mar 04 07:01:00 1993
- *** 205-211 ****
- ! function ExitWindows(Reserved: LongInt; ReturnCode: Word): Bool;
- --- 205-211 ----
- ! function ExitWindows(ReturnCode: LongInt; Reserved: Word): Bool;
-