home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
The Best of Mecomp Multimedia 1
/
Mecomp-CD.iso
/
amiga
/
tools
/
boot
/
fastexec
/
fastexec.s
< prev
Wrap
Text File
|
1997-05-21
|
75KB
|
4,483 lines
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
_DOSBase = 0
_ExpansionBase = _DOSBase+4
_UtilityBase = _ExpansionBase+4
Args = _UtilityBase+4
ArgsX = Args+4
ReturnCode = ArgsX+4
my_SIZEOF = ReturnCode+4
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
Start:
move.l (4).w,a6
move.l a0,a2
move.l d0,d2
moveq #my_SIZEOF/4-1,d1
.Clear
clr.l -(sp)
dbf d1,.Clear
move.l sp,a5
lea dos_library(pc),a1 ; library
moveq #0,d0 ; version
jsr -$0228(a6) ; _LVOOpenLibrary
move.l d0,_DOSBase(a5)
lea expansion_library(pc),a1; library
moveq #0,d0 ; version
jsr -$0228(a6) ; _LVOOpenLibrary
move.l d0,_ExpansionBase(a5)
cmp #36,$0014(a6) ; lib_Version
bcs .LibsOk
lea utility_library(pc),a1 ; library
moveq #0,d0 ; version
jsr -$0228(a6) ; _LVOOpenLibrary
move.l d0,_UtilityBase(a5)
.LibsOk
subq.l #1,d2
bls .Ok
cmp.b #'?',(a2)
beq Usage
cmp #36,$0014(a6) ; lib_Version
bcs .GetArgs
lea Template(pc),a1
move.l a1,d1 ; template
lea ArgArray(pc),a1
move.l a1,d2 ; array
moveq #0,d3 ; args
move.l a6,-(sp)
move.l _DOSBase(a5),a6
jsr -$031E(a6) ; _LVOReadArgs
tst.l d0
bne .ReadArgsOk
jsr -$0084(a6) ; _LVOIoErr
move.l d0,d1 ; code
moveq #0,d2 ; header
jsr -$01DA(a6) ; _LVOPrintFault
moveq #0,d0
.ReadArgsOk
move.l (sp)+,a6
move.l d0,Args(a5)
beq QuitError
move.l ArgSYSINFO(pc),d0
beq .ArgSYSINFOOk
bsr SysInfo
bra Quit
.ArgSYSINFOOk
move.l ArgCACHE(pc),d0
beq .ArgCACHEOk
move.l d0,a0
bsr XToI
lea CacheBits(pc),a0
move.l d0,(a0)
.ArgCACHEOk
movem.l d2-d7/a2-a4,-(sp)
lea AddMemData(pc),a4
move.l ArgADDMEM(pc),a3
moveq #15,d3
move.l a3,d0
beq .AddMem2
.AddMemLoop2
move.l (a3)+,d0
beq .AddMem2
move.l d0,a0
bsr XToI
move.l d0,d7 ; base
beq .AddMemErr2
move.l (a3)+,d0
beq .AddMemErr2
move.l d0,a0
bsr XToI
move.l d0,d4 ; size
beq .AddMemErr2
move.l (a3)+,d0
beq .AddMemErr2
move.l d0,a0
bsr XToIS
move.l d0,d5 ; attributes
beq .AddMemErr2
move.l (a3)+,d0
beq .AddMemErr2
move.l d0,a0
bsr XToIS
move.l d0,d6 ; priority
cmp.l #$FF,d6
bhi .AddMemErr2
movem.l d4-d7,(a4)
lea 16(a4),a4
dbf d3,.AddMemLoop2
bra .AddMem2
.AddMemErr2
movem.l (sp)+,d2-d7/a2-a4
lea TxtAddMem(pc),a0 ; string
bra QuitPutS
.AddMem2
movem.l (sp)+,d2-d7/a2-a4
bra .Ok
.GetArgs
move.l a2,a0
bsr GetArgs
move.l d0,ArgsX(a5)
bne .Args
lea TxtAllocMem(pc),a0 ; string
bra QuitPutS
.Args
move.l d0,d2
move.l d2,a0 ; args
lea StrSYSINFO(pc),a1 ; arg
bsr FindArg
tst.l d0
beq .SysInfo
bsr SysInfo
bra Quit
.SysInfo
move.l d2,a0 ; args
lea StrREBOOT(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgREBOOT(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrFASTSSP(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgFASTSSP(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrFASTVBR(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgFASTVBR(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrNOEXEC(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgNOEXEC(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrLOCAL(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgLOCAL(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrFASTEXP(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgFASTEXP(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrFASTMEM(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgFASTMEM(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrFASTINT(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgFASTINT(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrPATCH(pc),a1 ; arg
bsr FindArg
tst.l d0
lea ArgPATCH(pc),a0
sne (a0)
move.l d2,a0 ; args
lea StrCACHE(pc),a1 ; arg
bsr FindArg
tst.l d0
beq .Cache
lea ArgCACHE(pc),a0
st (a0)
move.l d0,d1
subq.l #1,d1
beq .Cache
move.l d0,a0
bsr XToI
move.l d0,CacheBits
.Cache
movem.l d2-d7/a2/a4,-(sp)
lea AddMemData(pc),a4
moveq #15,d3
move.l d2,a0 ; args
lea StrADDMEM(pc),a1 ; arg
bsr FindArg
tst.l d0
beq .AddMem
move.l d0,d1
subq.l #1,d1
beq .AddMem
move.l d0,a0
.AddMemLoop
bsr XToI
move.l d0,d7 ; base
beq .AddMem
bsr XToI
move.l d0,d4 ; size
beq .AddMemErr
bsr XToIS
move.l d0,d5 ; attributes
beq .AddMemErr
bsr XToIS
move.l d0,d6 ; priority
cmp.l #$FF,d6
bhi .AddMemErr
movem.l d4-d7,(a4)
lea 16(a4),a4
dbf d3,.AddMemLoop
bra .AddMem
.AddMemErr
movem.l (sp)+,d2-d7/a2/a4
lea TxtAddMem(pc),a0 ; string
bra QuitPutS
.AddMem
movem.l (sp)+,d2-d7/a2/a4
.Ok
bsr AddResident
tst.l d0
bgt ResidentOk
;Not enough memory?
lea TxtAllocMem(pc),a0
tst.l d0
beq QuitPutS
;FastExec already installed?
moveq #-1,d1
cmp.l d1,d0
beq Quit
;Can't find expansion.library?
lea TxtExpansion(pc),a0
moveq #-2,d1
cmp.l d1,d0
beq QuitPutS
ResidentOk
;FastExec installed okay
;If exec.library already is in fast memory, give a warning
;(except if NOEXEC option is used).
move.l ArgNOEXEC(pc),d0
bne Reboot
move.l a6,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
beq Reboot
lea TxtExec(pc),a0
bra QuitPutS
Reboot
move.l ArgREBOOT(pc),d0
beq Quit
bra OSColdReboot
QuitPutS
; a0=string
move.l a0,d1 ; str
bsr OSPutStr
QuitError
moveq #10,d0 ; RETURN_ERROR
move.l d0,ReturnCode(a5)
Quit:
move.l ArgsX(a5),a1 ; memoryBlock
bsr OSFreeVec
move.l Args(a5),d1 ; args
bsr OSFreeArgs
move.l _UtilityBase(a5),a1 ; library
bsr OSCloseLibrary
move.l _ExpansionBase(a5),a1 ; library
bsr OSCloseLibrary
move.l _DOSBase(a5),a1 ; library
bsr OSCloseLibrary
move.l ReturnCode(a5),d0
lea my_SIZEOF(sp),sp
rts
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
cnop 0,4
Resident:
move.l ArgCACHE(pc),d0
beq .Cache
move.l CacheBits(pc),d0 ; cacheBits
or #$2000,d0 ; CACRF_WriteAllocate
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
.Cache
bsr PatchLower
bsr PatchUpper
jsr -$0084(a6) ; _LVOForbid
moveq #0,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
move.l d0,-(sp)
;patch MakeLibrary() on KS 1.3 to longword align library bases.
cmp #36,$0014(a6) ; lib_Version
bcc .MakeLibraryOk
move.l a6,a1 ; library
lea MakeLibrary(pc),a0
move.l a0,d0 ; newFunction
move #-$0054,a0 ; funcOffset, _LVOMakeLibrary
jsr -$01A4(a6) ; _LVOSetFunction
.MakeLibraryOk
move.l ArgFASTEXP(pc),d0
beq .AddLibraryOk
move.l a6,a1 ; library
lea AddLibrary(pc),a0
move.l a0,d0 ; newFunction
move #-$018C,a0 ; funcOffset, _LVOAddLibrary
jsr -$01A4(a6) ; _LVOSetFunction
lea OldAddLibrary(pc),a0
move.l d0,(a0)
.AddLibraryOk
lea AddMemList(pc),a0
move.l ArgLOCAL(pc),d0
beq .AddMemList
lea AddMemListFlags(pc),a0
.AddMemList
move.l a6,a1 ; library
move.l a0,d0 ; newFunction
move #-$026A,a0 ; funcOffset, _LVOAddMemList
jsr -$01A4(a6) ; _LVOSetFunction
lea OldAddMemList(pc),a0
move.l d0,(a0)
bsr OSCacheClearU
move.l (sp)+,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
jsr -$008A(a6) ; _LVOPermit
movem.l d2/a2,-(sp)
lea AddMemData(pc),a2
.Mem
movem.l (a2)+,d0-d2/a0 ; size/attributes/pri/base
tst.l d0
beq .MemOk
lea FastExecName(pc),a1 ; name
jsr -$026A(a6) ; _LVOAddMemList
bra .Mem
.MemOk
movem.l (sp)+,d2/a2
rts
;------------------------------------------------------------------------------;
cnop 0,4
AddLibrary:
bsr .AddLibrary
bsr MoveExpansion
tst.l d0
beq .Rts
move.l a6,a1 ; library
move #-$018C,a0 ; funcOffset, _LVOAddLibrary
move.l OldAddLibrary(pc),d0 ; newFunction
jsr -$01A4(a6) ; _LVOSetFunction
.Rts
rts
.AddLibrary
move.l OldAddLibrary(pc),-(sp)
rts
OldAddLibrary
dc.l 0
;------------------------------------------------------------------------------;
cnop 0,4
AddMemListFlags:
or #$0100,d1 ; attributes, MEMF_LOCAL
; bra AddMemList
;------------------------------------------------------------------------------;
AddMemList:
;pretty useless checking
cmp #$0400,a0
bcs .Rts
cmp.l #$0028,d0 ; sizeof(MemHeader)+sizeof(MemChunk)
bcs .Rts
;If right (but not left) mouse button is held down, don't add any memory.
;This doesn't work for me when I use the original A1200 mouse...
; btst #6,$BFE001
; beq .LMB
; btst #10,$DFF016
; beq .Rts
;
;.LMB
;Check if memory has already been added
movem.l a2/a3,-(sp)
lea (a0,d0.l),a3
lea $0142(a6),a2 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),a2
tst.l (a2)
beq .Ok
cmp.l a2,a0
bcs .CS
cmp.l $0018(a2),a0 ; mh_Upper
bcc .Loop
bra .Quit
.CS
cmp.l a2,a3
bls .Loop
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,a2/a3
.Rts
rts
.Old
move.l OldAddMemList(pc),-(sp)
rts
.Ok
;save "attributes"
move.l d1,-(sp)
;add memory using the original function
bsr .Old
;I'm no expert on how to handle these caches, but
;I disassembled 68040.library, and it works this way:
;Forbid()
;oldCache=CacheControl(0,-1)
;patch stuff...
;CacheControl(oldCache,-1)
;Permit()
jsr -$0078(a6) ; _LVODisable
moveq #0,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
move.l d0,-(sp)
move.l ArgFASTMEM(pc),d0
beq .Chip
bsr MoveChipHeader
.Chip
move.l ArgNOEXEC(pc),d0
bne .Exec
bsr MoveExec
.Exec
move.l ArgFASTSSP(pc),d0
beq .SSP
bsr MoveSSP
.SSP
move.l ArgFASTVBR(pc),d0
beq .VBR
bsr MoveVBR
.VBR
move.l ArgFASTINT(pc),d0
beq .Int
bsr MoveIntrMem
.Int
move.l ArgPATCH(pc),d0
beq .Patch
bsr PatchForbid
bsr PatchSupervisorSafely
cmp #36,$0014(a6) ; lib_Version
bcs .Patch
bsr PatchExec
bsr PatchInterrupts
.Patch
bsr OSCacheClearU
move.l (sp)+,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
jsr -$007E(a6) ; _LVOEnable
move.l (sp)+,d1
and #4,d1 ; MEMF_FAST
beq .Quit
;fast memory has been added, replace our patch with the original AddMemList()
move.l a6,a1 ; library
move #-$026A,a0 ; funcOffset, _LVOAddMemList
move.l OldAddMemList(pc),d0 ; newFunction
jsr -$01A4(a6) ; _LVOSetFunction
bra .Quit
;------------------------------------------------------------------------------;
cnop 0,4
MakeLibrary:
movem.l d2-d7/a2/a3,-(sp)
move.l d0,d3
move.l a0,d4
move.l a1,d5
move.l a2,d6
move.l d1,d7
move.l a0,d2
beq .NegOk
move.l a0,a3
moveq #-1,d2
moveq #-1,d1
cmp (a3),d1
bne .Abs
addq.l #2,a3
.Rel
cmp (a3)+,d1
dbeq d2,.Rel
bra .Neg
.Abs
cmp.l (a3)+,d1
dbeq d2,.Abs
.Neg
not d2
mulu #6,d2
addq.l #3,d2
and #-4,d2
.NegOk
move.l d2,d0
add.l d3,d0 ; byteSize
move.l #$00010001,d1 ; requirements, MEMF_PUBLIC!MEMF_CLEAR
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
add.l d2,d0
move.l d0,a3
movem d2/d3,$0010(a3) ; lib_NegSize/lib_PosSize
move.l a3,a0 ; target
sub.l a2,a2 ; funcDispBase
move.l d4,a1 ; funcArray
cmp #-1,(a1)
bne .Make
addq.l #2,a1
move.l d4,a2
.Make
jsr -$005A(a6) ; _LVOMakeFunctions
tst.l d5
beq .Str
move.l a3,a2 ; memory
move.l d5,a1 ; initTable
moveq #0,d0 ; size
jsr -$004E(a6) ; _LVOInitStruct
.Str
move.l a3,d0 ; libAddr
tst.l d6
beq .End
move.l d6,a1 ; segList
move.l d7,a0
jsr (a1)
.End
movem.l (sp)+,d2-d7/a2/a3
rts
;------------------------------------------------------------------------------;
MoveChipHeader:
movem.l d2/a2/a3,-(sp)
jsr -$0084(a6) ; _LVOForbid
.Loop0
move.l $0142(a6),d2 ; MemList
.Loop1
move.l d2,a2
move.l (a2),d2
beq .Quit
move.l a2,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .Loop1
moveq #$0020,d0 ; byteSize, sizeof(MemHeader)
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .Quit
move.l d0,a3
lea $0008(a2),a0 ; source, mh_Attributes
lea $0008(a3),a1 ; dest, mh_Attributes
moveq #$0018,d0 ; size, sizeof(MemHeader)-ln_Type
jsr -$0270(a6) ; _LVOCopyMem
lea $0020(a2),a0 ; sizeof(MemHeader)
cmp.l $0014(a2),a0 ; mh_Lower
bne .Ok
move.l a2,$0014(a3) ; mh_Lower
.Ok
move.l a2,a1 ; node
jsr -$00FC(a6) ; _LVORemove
lea $0142(a6),a0 ; list, MemList
move.l a3,a1 ; node
jsr -$010E(a6) ; _LVOEnqueue
cmp #36,$0014(a6) ; lib_Version
bcs .Loop0
move.l a2,a1 ; memoryBlock
moveq #$0020,d0 ; byteSize, sizeof(MemHeader)
bsr FreeMemSafely
bra .Loop0
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,d2/a2/a3
rts
;------------------------------------------------------------------------------;
MoveExec:
movem.l d0-a6,-(sp)
move.l a6,a2
move.l a6,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .End
moveq #0,d2
moveq #0,d3
movem $0010(a6),d2/d3 ; lib_NegSize/lib_PosSize
addq.l #3,d2
and #-4,d2
move.l d2,d0
add.l d3,d0 ; byteSize
move.l #$00010005,d1 ; MEMF_PUBLIC!MEMF_FAST!MEMF_CLEAR
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a3
move.l a6,a1 ; node
jsr -$00FC(a6) ; _LVORemove
move.l a6,a0 ; source
move.l a3,a1 ; dest
move.l d2,d0 ; size
sub.l d0,a0
add.l d3,d0
jsr -$0270(a6) ; _LVOCopyMem
bsr OSCacheClearU
add.l d2,a3
move d2,$0010(a3) ; lib_NegSize
move.l a3,a6
bsr InitChkBase
bsr InitChkSum
lea .ListTable(pc),a4
.ListLoop
move (a4)+,d0
beq .ListOk
bsr InitList
bra .ListLoop
.ListTable
dc.w $0142 ; MemList
dc.w $0150 ; ResourceList
dc.w $015E ; DeviceList
dc.w $016C ; IntrList
dc.w $017A ; LibList
dc.w $0188 ; PortList
dc.w $0196 ; TaskReady
dc.w $01A4 ; TaskWait
dc.w $01B2 ; SoftInts
dc.w $01C2
dc.w $01D2
dc.w $01E2
dc.w $01F2
dc.w $0214 ; SemaphoreList
dc.w 0
.ListOk
cmp #39,$0014(a6) ; lib_Version
bcs .List39
move #$0268,d0 ; ex_MemHandlers
bsr InitList
.List39
;Replace _ExecBase-pointers on stack
move.l sp,a0
moveq #127,d1
.Repl
addq.l #2,a0
cmp.l (a0),a2
dbeq d1,.Repl
bne .ReplOk
move.l a6,(a0)
bra .Repl
.ReplOk
;Replace _ExecBase-pointer in _ExpansionBase V33/34 (offset $0024)
;_ExpansionBase has not been added to library list, get it from the stack
;offset should be
; 4 (expansion jumps to addmemlist)
; 8 (addmemlist routine saves a2/a3)
; 4 (addmemlist saves attributes
; 4 (addmemlist routine saves cachebits)
; 4 (addmemlist routine jumps to this routine)
;60 (this routine saves d0-a6)
;--
;84
;_ExpansionBase V36+ doesn't cache _SysBase
cmp #36,$0014(a6) ; lib_Version
bcc .ExpOk
move.l 84(sp),d0
btst #0,d0
bne .ExpErr
move.l d0,a1 ; address
move.l a1,-(sp)
jsr -$0216(a6) ; _LVOTypeOfMem
move.l (sp)+,a1
tst.l d0
beq .ExpErr
cmp.l $0024(a1),a2 ; eb_ExecBase
bne .ExpErr
move.l a6,$0024(a1) ; eb_ExecBase
bra .ExpOk
.ExpErr
lea FlagEBExec(pc),a0
st (a0)
.ExpOk
move.l a6,(4).w
move.l a6,a1 ; library
or.b #2,$000E(a1) ; lib_Flags, LIBF_CHANGED
jsr -$018C(a6) ; _LVOAddLibrary
move.l a2,a1 ; memoryBlock
moveq #0,d0 ; byteSize
move $0010(a2),d0 ; lib_NegSize
sub.l d0,a1
add $0012(a2),d0 ; lib_PosSize
cmp #36,$0014(a6) ; lib_Version
bcc .Free
and #-8,d0
move.b FlagEBExec(pc),d1
bne .End
.Free
bsr FreeMemSafely
.End
movem.l (sp)+,d0-a6
rts
;------------------------------------------------------------------------------;
MoveExpansion:
; out d0=library
;a2=old base
;a3=new base
movem.l d2/d3/a2-a4,-(sp)
jsr -$0084(a6) ; _LVOForbid
lea $017A(a6),a0 ; list, LibList
lea expansion_library(pc),a1; name
jsr -$0114(a6) ; _LVOFindName
tst.l d0
beq .Err
move.l d0,a2
move.l a2,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .Err
moveq #0,d2
moveq #0,d3
movem $0010(a2),d2/d3 ; lib_NegSize/lib_PosSize
addq.l #3,d2
and #-4,d2
move.l d2,d0
add.l d3,d0 ; byteSize
move.l #$00010005,d1 ; MEMF_PUBLIC!MEMF_FAST!MEMF_CLEAR
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .Err
move.l d0,a3
move.l a2,a1 ; node
jsr -$00FC(a6) ; _LVORemove
move.l a2,a0 ; source
move.l a3,a1 ; dest
move.l d2,d0 ; size
sub.l d0,a0
add.l d3,d0
jsr -$0270(a6) ; _LVOCopyMem
bsr OSCacheClearU
add.l d2,a3
move d2,$0010(a3) ; lib_NegSize
bsr .Fix
move.l a3,a1 ; library
or.b #2,$000E(a1) ; lib_Flags, LIBF_CHANGED
jsr -$018C(a6) ; _LVOAddLibrary
move.l a2,a1 ; memoryBlock
moveq #0,d0 ; byteSize
move $0010(a2),d0 ; lib_NegSize
sub.l d0,a1
add $0012(a2),d0 ; lib_PosSize
bsr FreeMemSafely
move.l a3,d0
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,d2/d3/a2-a4
rts
.Err
moveq #0,d0
bra .Quit
.Fix
moveq #$003C,d0 ; eb_ConfigDevList
bsr InitList
moveq #$004A,d0 ; eb_MountList
bsr InitList
move #$0168,d0 ; eb_BindSemaphore+ss_WaitQueue
bsr InitList
cmp #36,$0014(a6) ; lib_Version
bcc .Rts
move.l a6,$0024(a3) ; eb_ExecBase
.Rts
rts
;------------------------------------------------------------------------------;
;Don't ask me what I'm doing here...
MoveIntrMem:
movem.l d2/d4/a2-a4,-(sp)
move.l 3*12+$0054(a6),a4
moveq #$50,d4
cmp #36,$0014(a6) ; lib_Version
bcc .Size
moveq #$6E,d4
.Size
move.l a4,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .End
move.l d4,d0 ; byteSize
move.l #$00010005,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST!MEMF_CLEAR
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
lea .Table(pc),a3
moveq #4,d2
jsr -$0078(a6) ; _LVODisable
.Loop
move.l a2,a1
lea $000E(a2),a2
move (a3)+,d0
mulu #12,d0
move.l $54(a6,d0.l),a0
move.l a1,$54(a6,d0.l)
move $000E(a0),(a2)+
cmp #36,$0014(a6) ; lib_Version
bcc .Copy
move $0010(a0),(a2)+
move.l $0012(a0),(a2)+
.Copy
bsr CopyList
dbf d2,.Loop
jsr -$007E(a6) ; _LVOEnable
move.l a4,a1 ; memoryBlock
move.l d4,d0 ; byteSize
bsr FreeMemSafely
.End
movem.l (sp)+,d2/d4/a2-a4
rts
.Table
dc.w 3,5,4,13,15
;------------------------------------------------------------------------------;
MoveSSP:
movem.l d2/a2,-(sp)
jsr -$0084(a6) ; _LVOForbid
move.l $003A(a6),a2 ; SysStkLower
move.l $0036(a6),d2 ; SysStkUpper
sub.l a2,d2
move.l a2,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .Err
move.l d2,d0 ; byteSize
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_CLEAR
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .Err
bsr SetSSP
jsr -$008A(a6) ; _LVOPermit
move.l a2,a1 ; memoryBlock
move.l d2,d0 ; byteSize
bsr FreeMemSafely
.End
movem.l (sp)+,d2/a2
rts
.Err
jsr -$008A(a6) ; _LVOPermit
bra .End
;------------------------------------------------------------------------------;
MoveVBR:
move.l a2,-(sp)
btst #0,$0129(a6) ; AttnFlags+1, AFB_68010
beq .End
moveq #1,d0 ; byteSize
ror #6,d0 ; 1024
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
jsr -$0084(a6) ; _LVOForbid
bsr GetVBR
move.l d0,a1 ; address
bsr MyTypeOfMem
and #4,d0 ; MEMF_FAST
bne .Err
move.l d0,a0
move.l a2,a1
move #255,d0
.Loop
move.l (a0)+,(a1)+
dbf d0,.Loop
move.l a2,d0
bsr SetVBR
jsr -$008A(a6) ; _LVOPermit
.End
move.l (sp)+,a2
rts
.Err
jsr -$008A(a6) ; _LVOPermit
move.l a2,a1 ; memoryBlock
moveq #1,d0 ; byteSize
ror #6,d0 ; 1024
jsr -$00D2(a6) ; _LVOFreeMem
bra .End
;------------------------------------------------------------------------------;
;modify all
; move.l #0,a6
;to move _ExecBase instead of zero.
PatchA6:
; a0=buff
; d0=size
move.l a0,a1
add.l d0,a1
.Loop
cmp.l a1,a0
bcc .Rts
cmp #$2C7C,(a0)+ ; move.l #x,a6
bne .Loop
tst.l (a0)
bne .Loop
move.l a6,(a0)+
bra .Loop
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
PatchExec:
movem.l a2/a3,-(sp)
; cmp #36,$0014(a6) ; lib_Version
; bcs .End
move.l #PatchExecEnd-PatchExecStart,d0; byteSize
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
lea PatchExecStart(pc),a0 ; source
move.l d0,a1 ; dest
move.l #PatchExecEnd-PatchExecStart,d0; size
jsr -$0276(a6) ; _LVOCopyMemQuick
move.l a2,a0 ; buff
move.l #PatchExecEnd-PatchExecStart,d0; size
bsr PatchA6
lea Exception4-PatchExecStart(a2),a0
move.l a0,2+Exception2-PatchExecStart(a2)
btst #0,$0129(a6) ; AttnFlags+1, AFB_68010
bne .Switch
move.l #$4E714E71,8+Exception2-PatchExecStart(a2); nop/nop
move #$5C8F,4+Exception5-PatchExecStart(a2); addq.l #6,sp
.Switch
moveq #$70,d0 ; AFF_68881!AFF_68882!AFF_FPU40
and $0128(a6),d0 ; AttnFlags
bne .SwitchFPU
move.l a6,a1 ; library
lea Switch-PatchExecStart(a2),a0
move.l a0,d0 ; newFunction
move #-$0036,a0 ; funcOffset, _LVOSwitch
jsr -$01A4(a6) ; _LVOSetFunction
bra .SwitchOk
.SwitchFPU
move.l a6,a1 ; library
lea SwitchFPU-PatchExecStart(a2),a0
move.l a0,d0 ; newFunction
move #-$0036,a0 ; funcOffset, _LVOSwitch
jsr -$01A4(a6) ; _LVOSetFunction
.SwitchOk
lea .Table(pc),a3
.Loop
tst.l (a3)
beq .End
move (a3)+,d0
ext.l d0
add.l a2,d0 ; newFunction
move (a3)+,a0 ; funcOffset
move.l a6,a1 ; library
jsr -$01A4(a6) ; _LVOSetFunction
bra .Loop
.End
movem.l (sp)+,a2/a3
rts
cnop 0,4
.Table
dc.w Cause-PatchExecStart
dc.w -$00B4 ; _LVOCause
dc.w ExitIntr-PatchExecStart
dc.w -$0024 ; _LVOExitIntr
dc.w PutMsg-PatchExecStart
dc.w -$016E ; _LVOPutMsg
dc.w ReplyMsg-PatchExecStart
dc.w -$017A ; _LVOReplyMsg
dc.w Schedule-PatchExecStart
dc.w -$002A ; _LVOSchedule
dc.w Dispatch-PatchExecStart
dc.w -$003C ; _LVODispatch
dc.w Exception-PatchExecStart
dc.w -$0042 ; _LVOException
dc.w Wait-PatchExecStart
dc.w -$013E ; _LVOWait
dc.l 0
;------------------------------------------------------------------------------;
;put the code "addq.b #1,$0127(a6)/rts" directly in the jump table
PatchForbid:
lea Forbid(pc),a0
move.l a0,d0 ; newFunction
move.l a6,a1 ; library
move #-$0084,a0 ; funcOffset, _LVOForbid
; bra PatchTable
PatchTable:
lea 0(a1,a0),a0
move.l a1,-(sp)
jsr -$0084(a6) ; _LVOForbid
or.b #2,$000E(a1) ; lib_Flags, LIBF_CHANGED
move.l d0,a1
move.l (a1)+,(a0)+
move (a1),(a0)
bsr OSCacheClearU
jsr -$008A(a6) ; _LVOPermit
move.l (sp)+,a1 ; library
jmp -$01AA(a6) ; _LVOSumLibrary
Forbid:
addq.b #1,$0127(a6) ; TDNestCnt
rts
;------------------------------------------------------------------------------;
;In the patches for the interrupt routines
;I try to avoid btst-instructions,
;put _ExecBase directly in the move instruction instead reading it from $4
;and some other changes.
;The interrupts and exec.library/ExitIntr() don't work the same
;between KS 1.3 and 2.0, so this only patches 2.0 and up.
PatchInterrupts:
move.l a2,-(sp)
; cmp #36,$0014(a6) ; lib_Version
; bcs .End
move.l #.EndLabel-.StartLabel,d0; byteSize
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
lea .StartLabel(pc),a0 ; source
move.l d0,a1 ; dest
move.l #.EndLabel-.StartLabel,d0; size
jsr -$0276(a6) ; _LVOCopyMemQuick
move.l a2,a0 ; buffer
move.l #.EndLabel-.StartLabel,d0; size
bsr PatchA6
jsr -$027C(a6) ; _LVOCacheClearU
jsr -$0084(a6) ; _LVOForbid
bsr GetVBR
move.l d0,a1
lea .Int1-.StartLabel(a2),a0
move.l a0,$64(a1)
lea .Int2-.StartLabel(a2),a0
move.l a0,$68(a1)
lea .Int3-.StartLabel(a2),a0
move.l a0,$6C(a1)
lea .Int4-.StartLabel(a2),a0
move.l a0,$70(a1)
lea .Int5-.StartLabel(a2),a0
move.l a0,$74(a1)
lea .Int6-.StartLabel(a2),a0
move.l a0,$78(a1)
lea .Int7-.StartLabel(a2),a0
move.l a0,$7C(a1)
jsr -$027C(a6) ; _LVOCacheClearU
jsr -$008A(a6) ; _LVOPermit
; moveq #1,d0
.End
move.l (sp)+,a2
rts
cnop 0,4
.StartLabel
cnop 0,4
; 0 => $0054
; 1 => $0060
; 2 => $006C
; 3 => $0078
; 4 => $0084
; 5 => $0090
; 6 => $009C
; 7 => $00A8
; 8 => $00B4
; 9 => $00C0
;10 => $00CC
;11 => $00D8
;12 => $00E4
;13 => $00F0
;14 => $00FC
.Int1:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done1
moveq #1,d0
and.l d1,d0
beq .Next1a
move.l #0,a6
movem.l $0054(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next1a
moveq #2,d0
and.l d1,d0
beq .Next1b
move.l #0,a6
movem.l $0060(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next1b
moveq #4,d0
and.l d1,d0
beq .Done1
move.l #0,a6
movem.l $006C(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Done1
movem.l (sp)+,d0/d1/a0
lea 12(sp),sp
rte
cnop 0,4
.Int2:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done1
moveq #8,d0
and.l d1,d0
beq .Done1
move.l #0,a6
movem.l $0078(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Int3:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done3
moveq #64,d0
and.l d1,d0
beq .Next3a
move.l #0,a6
movem.l $009C(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next3a
moveq #32,d0
and.l d1,d0
beq .Next3b
move.l #0,a6
movem.l $0090(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next3b
moveq #16,d0
and.l d1,d0
beq .Done3
move.l #0,a6
movem.l $0084(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Done3
movem.l (sp)+,d0/d1/a0
lea 12(sp),sp
rte
cnop 0,4
.Int4:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done3
move.l #0,a6
.Loop4
btst #8,d1
beq .Next4a
movem.l $00B4(a6),a1/a5
move.l a6,-(sp)
pea .Quit4(pc)
jmp (a5)
cnop 0,4
.Next4a
btst #10,d1
beq .Next4b
movem.l $00CC(a6),a1/a5
move.l a6,-(sp)
pea .Quit4(pc)
jmp (a5)
cnop 0,4
.Next4b
tst.b d1
bpl .Next4c
movem.l $00A8(a6),a1/a5
move.l a6,-(sp)
pea .Quit4(pc)
jmp (a5)
cnop 0,4
.Next4c
btst #9,d1
beq .Next4d
movem.l $00C0(a6),a1/a5
move.l a6,-(sp)
pea .Quit4(pc)
jmp (a5)
cnop 0,4
.Next4d
movem.l (sp)+,d0/d1/a0/a1/a5/a6
rte
cnop 0,4
.Quit4
move.l (sp)+,a6
lea $DFF000,a0
move #$0780,d1
and $001C(a0),d1
and $001E(a0),d1
bne .Loop4
move.l a6,-(sp)
jmp -$0024(a6) ; _LVOExitIntr
cnop 0,4
.Int5:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done5
btst #12,d1
beq .Next5a
move.l #0,a6
movem.l $00E4(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next5a
btst #11,d1
beq .Done5
move.l #0,a6
movem.l $00D8(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Done5
movem.l (sp)+,d0/d1/a0
lea 12(sp),sp
rte
cnop 0,4
.Int6:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move.l $001C(a0),d0
move.l d0,d1
swap d0
and.l d0,d1
add d0,d0
bpl .Done5
move.l d1,d0
add d0,d0
bpl .Next6a
move.l #0,a6
movem.l $00FC(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next6a
btst #13,d1
beq .Done5
move.l #0,a6
movem.l $00F0(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Int7:
rte
cnop 0,4
.EndLabel
;------------------------------------------------------------------------------;
;Patch exec.library/Supervisor()
;On KS 1.3 and MC68000, change
; pea LB_00FC08F4
;to
; pea LB_00FC08F4(pc)
;On MC68010+, change
; subq.l #8,sp
; move sr,(sp)
; move.l #LB_00F80B3C,2(sp)
; move #$0020,6(sp)
;to
; move #$0020,-(sp)
; pea LB_00F80B3C(pc)
; move sr,-(sp)
PatchSupervisorSafely:
jsr -$0084(a6) ; _LVOForbid
move.l 2-$001E(a6),a0 ; _LVOSupervisor
cmp.l #$007C2000,(a0)+ ; or #$2000,sr
bne .Quit
cmp #$4879,(a0) ; pea x
beq .Old ; KS 1.3/68000
cmp #$487A,(a0) ; pea x(pc)
beq .Quit ; KS 2.0/68000
cmp.l #$518F40D7,(a0)+ ; subq.l #8,sp; move sr,(sp)
bne .Quit
cmp #$2F7C,(a0)+ ; move.l #x,2(sp)
bne .Quit
addq.l #4,a0 ; x
cmp #2,(a0)+ ; 2
bne .Quit
cmp.l #$3F7C0020,(a0)+ ; move.w #$0020,6(sp)
bne .Quit
cmp.l #$00064ED5,(a0) ; 6; jmp (a5)
bne .Quit
bra .Ok
.Old
addq.l #6,a0 ; pea x
cmp.l #$40E74ED5,(a0) ; move sr,-(sp); jmp (a5)
bne .Quit
.Ok
bsr PatchSupervisor
.Quit
jmp -$008A(a6) ; _LVOPermit
;------------------------------------------------------------------------------;
PatchSupervisor:
move.l a2,-(sp)
move.l #SupervisorEnd-Supervisor,d0; byteSize
moveq #5,d1 ; requirements, MEMF_PUBLIC!MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
lea Supervisor(pc),a0 ; source
move.l d0,a1 ; dest
move.l #SupervisorEnd-Supervisor,d0; size
jsr -$0276(a6) ; _LVOCopyMemQuick
lea SupervisorRts-Supervisor(a2),a0
move.l a0,12+Exception8-Supervisor(a2)
jsr -$0084(a6) ; _LVOForbid
bsr GetVBR
move.l d0,a1
lea Exception8-Supervisor(a2),a0
move.l a0,$20(a1)
move.l a2,a0
btst #0,$0129(a6) ; AttnFlags+1, AFB_68010
bne .Ok
move.l (a0)+,(a0)
.Ok
move.l a0,2+Exception8-Supervisor(a2)
move.l a6,a1 ; library
move.l a0,d0 ; newFunction
move #-$001E,a0 ; funcOffset, _LVOSupervisor
jsr -$01A4(a6) ; _LVOSetFunction
jsr -$008A(a6) ; _LVOPermit
moveq #1,d0
.End
move.l (sp)+,a2
rts
cnop 0,4
Supervisor:
or #$2000,sr
move #$0020,-(sp)
pea SupervisorRts(pc)
move sr,-(sp)
jmp (a5)
cnop 0,4
SupervisorRts
rts
cnop 0,4
Exception8:
cmp.l #0,2(sp)
bne.s .Err
move.l #0,2(sp)
jmp (a5)
.Err
or #$0700,sr
move.l #8,-(sp)
btst #5,4(sp)
bne .Alert
subq.l #4,sp
move.l a0,-(sp)
move.l (4).w,a0
move.l $0114(a0),a0 ; ThisTask
move.l $0032(a0),4(sp) ; tc_TrapCode
move.l (sp)+,a0
rts
.Alert
move.l (sp)+,d7 ; alertNum
bset #31,d7
move.l (4).w,a6
jmp -$006C(a6) ; _LVOAlert
cnop 0,4
SupervisorEnd
;------------------------------------------------------------------------------;
;On KS 1.3 mh_Lower for chip mem points to memory after exec.library,
;set it to $400 as in later kickstarts.
PatchLower:
cmp #36,$0014(a6) ; lib_Version
bcc .Rts
move.l #$0427,d1
add $0010(a6),d1 ; lib_NegSize
add $0012(a6),d1 ; lib_PosSize
and #-8,d1
lea $0142(a6),a0 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a0),a0
tst.l (a0)
beq .Quit
cmp.l $0014(a0),d1 ; mh_Lower
bne .Loop
move.l #$0400,$0014(a0) ; mh_Lower
.Quit
jmp -$008A(a6) ; _LVOPermit
.Rts
rts
;------------------------------------------------------------------------------;
;On KS 1.3 the supervisor stack comes right after mh_Upper.
PatchUpper:
cmp #36,$0014(a6) ; lib_Version
bcc .Rts
move.l $003A(a6),d1 ; SysStkLower
lea $0142(a6),a0 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a0),a0
tst.l (a0)
beq .Quit
cmp.l $0018(a0),d1 ; mh_Upper
bne .Loop
move.l $0036(a6),$0018(a0) ; mh_Upper, SysStkUpper
.Quit
jmp -$008A(a6) ; _LVOPermit
.Rts
rts
;------------------------------------------------------------------------------;
InitList:
; a2=old base
; a3=new base
; d0=offset
lea (a2,d0),a0
lea (a3,d0),a1
; bra CopyList
;------------------------------------------------------------------------------;
CopyList:
move.l a2,d1
move.l (a0),a2
move.l a2,(a1)
move.l a1,$0004(a2)
move.l $0008(a0),a2
move.l a2,$0008(a1)
addq.l #4,a1
move.l a1,(a2)
move.l d1,a2
rts
;------------------------------------------------------------------------------;
;Only free memory if it is within any Lower/Upper bound
FreeMemSafely:
move.l d0,d1
beq .Rts
add.l a1,d1
lea $0142(a6),a0 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a0),a0
tst.l (a0)
beq .Quit
cmp.l $0014(a0),a1 ; mh_Lower
bcs .Loop
cmp.l $0018(a0),a1 ; mh_Upper
bcc .Loop
cmp.l $0018(a0),d1 ; mh_Upper
bhi .Quit
jsr -$00D2(a6) ; _LVOFreeMem
.Quit
jmp -$008A(a6) ; _LVOPermit
.Rts
rts
;------------------------------------------------------------------------------;
GetVBR:
; out d0=vbr
moveq #0,d0
btst #0,$0129(a6) ; AttnFlags+1, AFB_68010
beq .Rts
move.l a5,a0
lea .Ok(pc),a5 ; userFuntion
jsr -$001E(a6) ; _LVOSupervisor
move.l a0,a5
.Rts
rts
.Ok
dc.l $4E7A0801 ; movec vbr,d0
rte
;------------------------------------------------------------------------------;
InitChkBase:
move.l a6,d1
not.l d1
move.l $0026(a6),d0 ; ChkBase
move.l d1,$0026(a6) ; ChkBase
rts
;------------------------------------------------------------------------------;
InitChkSum:
moveq #0,d1
lea $0022(a6),a0 ; SoftVer
moveq #23,d0
.Loop
add (a0)+,d1
dbf d0,.Loop
not d1
move (a0),d0
move d1,(a0)
rts
;------------------------------------------------------------------------------;
MyTypeOfMem:
; a1=address
; out d0=type
;MEMB_SLOW=0
;MEMB_CHIP=1
;MEMB_FAST=2
moveq #2,d0 ; MEMF_CHIP
cmp.l #$00200000,a1 ; 0-2MB
bcs .Rts ; lower than=>chip
cmp.l #$00C00000,a1 ; start of ranger memory
bcs .Ok
moveq #1,d0 ; MEMF_SLOW
cmp.l #$00DC0000,a1 ; end of ranger memory
bcs .Rts
.Ok
jsr -$0216(a6) ; _LVOTypeOfMem
and.l #6,d0 ; MEMF_CHIP!MEMF_FAST (wipe out our slow flag)
bne .Rts
moveq #4,d0 ; MEMF_FAST
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSCacheClearE:
cmp #37,$0014(a6) ; lib_Version
bcs .Old
jmp -$0282(a6) ; _LVOCacheClearE
.Old
btst #1,$0129(a6) ; AttnFlags+1, AFB_68020
beq .Rts
and.l #$00000808,d1 ; caches, CACRF_ClearI!CACRF_ClearD
move.l a5,a0
lea .F2(pc),a5 ; userFunction
btst #3,$0129(a6) ; AttnFlags+1, AFB_68040
beq .Ok
lea .F4(pc),a5 ; userFunction
btst #3,d1 ; CACRB_ClearI
beq .Ok
lea .F4I(pc),a5
.Ok
jsr -$001E(a6) ; _LVOSupervisor
move.l a0,a5
.Rts
rts
.F2
or #$0700,sr
dc.l $4E7A0002 ; movec cacr,d0
or.l d1,d0
dc.l $4E7B0002 ; movec d0,cacr
rte
.F4
dc.w $F478
rte
.F4I
dc.w $F4F8
rte
;------------------------------------------------------------------------------;
cnop 0,4
OSCacheClearU:
cmp #37,$0014(a6) ; lib_Version
bcs .Old
jmp -$027C(a6) ; _LVOCacheClearU
.Old
move.l #$00000808,d1 ; caches, CACRF_ClearI!CACRF_ClearD
bra OSCacheClearE
;------------------------------------------------------------------------------;
cnop 0,4
OSCacheControl:
cmp #37,$0014(a6) ; lib_Version
bcs .Old
jmp -$0288(a6) ; _LVOCacheControl
.Old
movem.l d2/a5,-(sp)
move.l d0,d2
moveq #0,d0
btst #1,$0129(a6) ; AttnFlags+1, AFB_68020
beq .End
and.l d1,d2
not.l d1
or #$0808,d2 ; CACRF_ClearI|CACRF_ClearD
lea .F(pc),a5 ; userFunction
jsr -$001E(a6) ; _LVOSupervisor
.End
movem.l (sp)+,d2/a5
rts
.F
or #$0700,sr
dc.l $4E7A0002 ; movec cacr,d0
and.l d0,d1
or.l d2,d1
nop
dc.l $4E7B1002 ; movec d1,cacr
nop
rte
;------------------------------------------------------------------------------;
SetSSP:
; d0=ptr
movem.l d2/a5,-(sp)
lea .Ok(pc),a5 ; userFunction
jsr -$001E(a6) ; _LVOSupervisor
movem.l (sp)+,d2/a5
bra InitChkSum
.Ok
or #$0700,sr
move.l $003A(a6),a0 ; SysStkLower
move.l d0,a1
move.l $0036(a6),d2 ; SysStkUpper
sub.l a0,d2
move.l d2,d1
lsr.l #2,d1
subq.l #1,d1
.Copy
move.l (a0)+,(a1)+
dbf d1,.Copy
sub.l $003A(a6),sp ; SysStkLower
add.l d0,sp
move.l d0,$003A(a6) ; SysStkLower
add.l d2,d0
move.l d0,$0036(a6) ; SysStkUpper
rte
;------------------------------------------------------------------------------;
SetVBR:
; d0=vbr
btst #0,$0129(a6) ; AttnFlags+1, AFB_68010
beq .Rts
move.l a5,a0
lea .Ok(pc),a5 ; userFuntion
jsr -$001E(a6) ; _LVOSupervisor
move.l a0,a5
.Rts
rts
.Ok
dc.l $4E7B0801 ; movec d0,vbr
rte
;------------------------------------------------------------------------------;
cnop 0,4
PatchExecStart
;------------------------------------------------------------------------------;
cnop 0,4
Cause:
moveq #11,d0 ; NT_SOFTINT
move #$00F0,d1
lea $01DA(a6),a0
move #$4000,$DFF09A ; intena
cmp.b $0008(a1),d0 ; ln_Type
beq .1
move.b d0,$0008(a1) ; ln_Type
and.b $0009(a1),d1 ; ln_Pri
ext d1
add d1,a0
move.l (a0),d0
move.l a1,(a0)
subq.l #4,a0
exg.l d0,a0
movem.l d0/a0,(a1)
move.l a1,(a0)
move #$8004,$DFF09C ; intreq
or #$2000,$0124(a6) ; SysFlags
.1
tst.b $0126(a6) ; IDNestCnt
bge .2
move #$C000,$DFF09A ; intena
.2
nop
rts
;------------------------------------------------------------------------------;
cnop 0,4
ExitIntr:
move.l (sp)+,a6
moveq #$20,d0
and.b $0018(sp),d0
bne ExitIntr1
tst.b $0127(a6) ; TDNestCnt
bge ExitIntr1
tst $0124(a6) ; SysFlags
bmi ExitIntr2
ExitIntr1
movem.l (sp)+,d0/d1/a0/a1/a5/a6
rte
cnop 0,4
ExitIntr2
move #$2000,sr
bra Schedule1
cnop 0,4
Schedule:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
Schedule1
move.l $0114(a6),a1 ; ThisTask
move #$2700,sr
and #$7FFF,$0124(a6) ; SysFlags
moveq #$20,d0 ; TF_EXCEPT
and.b $000E(a1),d0 ; tc_Flags
bne .2
lea $0196(a6),a0 ; TaskReady
cmp.l $0008(a0),a0
beq ExitIntr1
move.l (a0),a0
move.b $0009(a0),d1 ; ln_Pri
cmp.b $0009(a1),d1 ; ln_Pri
bgt .2
moveq #$40,d0
and.b $0124(a6),d0 ; SysFlags
beq ExitIntr1
.2
lea $0196(a6),a0 ; TaskReady
move.b $0009(a1),d1 ; ln_Pri
move.l (a0),d0
.3
move.l d0,a0
move.l (a0),d0
beq .4
cmp.b $0009(a0),d1 ; ln_Pri
ble .3
.4
move.l $0004(a0),d0
move.l a1,$0004(a0)
exg.l d0,a0
movem.l d0/a0,(a1)
move.l a1,(a0)
move.b #3,$000F(a1) ; tc_State, TS_READY
move #$2000,sr
movem.l (sp)+,d0/d1/a0/a1/a5
move.l (sp),-(sp)
move.l -$0034(a6),4(sp)
move.l (sp)+,a6
rts
;------------------------------------------------------------------------------;
cnop 0,4
ReplyMsg:
moveq #7,d0 ; NT_REPLYMSG
move.l $000E(a1),d1 ; mn_ReplyPort
move.l d1,a0
bne Msg
move.b #6,$0008(a1) ; ln_Type, NT_FREEMSG
rts
cnop 0,4
PutMsg:
moveq #5,d0 ; NT_MESSAGE
move.l a0,d1
Msg
lea $001C(a0),a0 ; mp_MsgList+8
move #$4000,$DFF09A ; intena
addq.b #1,$0126(a6) ; IDNestCnt
move.b d0,$0008(a1) ; ln_Type
move.l (a0),d0
move.l a1,(a0)
subq.l #4,a0
exg.l d0,a0
movem.l d0/a0,(a1)
move.l a1,(a0)
move.l d1,a0
move.l $0010(a0),d0 ; mp_SigTask
beq .1
moveq #3,d1 ; PF_ACTION
and.b $000E(a0),d1 ; mp_Flags
beq .6
subq.l #1,d1 ; PA_SOFTINT=1
bne .3
move.l d0,a1 ; interrupt
jsr -$00B4(a6) ; _LVOCause
.1
subq.b #1,$0126(a6) ; IDNestCnt
bge .2
move #$C000,$DFF09A ; intena
.2
rts
cnop 0,4
.3
subq.l #1,d1 ; PA_IGNORE=2
beq .4
move.l d0,a1
jsr (a1)
.4
subq.b #1,$0126(a6) ; IDNestCnt
bge .5
move #$C000,$DFF09A ; intena
.5
rts
cnop 0,4
.6
move.b $000F(a0),d1 ; mp_SigBit
addq.b #1,$0127(a6) ; TDNestCnt
subq.b #1,$0126(a6) ; IDNestCnt
bge .7
move #$C000,$DFF09A ; intena
.7
move.l d0,a1 ; task
moveq #0,d0 ; signalSet
bset d1,d0
jsr -$0144(a6) ; _LVOSignal
jmp -$008A(a6) ; _LVOPermit
;------------------------------------------------------------------------------;
cnop 0,4
Switch:
move #$2000,sr
move.l a5,-(sp)
move.l usp,a5
movem.l d0-a6,-(a5)
move.l #0,a6
move $0126(a6),d0 ; IDNestCnt
move #-1,$0126(a6) ; IDNestCnt
move #$C000,$DFF09A ; intena
move.l (sp)+,$0034(a5)
move (sp)+,-(a5)
move.l (sp)+,-(a5)
move.l $0230(a6),a4 ; ex_LaunchPoint
move.l $0114(a6),a3 ; ThisTask
move d0,$0010(a3) ; tc_IDNestCnt
move.l a5,$0036(a3) ; tc_SPReg
moveq #$40,d0 ; TF_SWITCH
and.b $000E(a3),d0 ; tc_Flags
beq Dispatch1
move.l $0042(a3),a5 ; tc_Switch
jsr (a5)
bra Dispatch1
;------------------------------------------------------------------------------;
cnop 0,4
SwitchFPU:
move #$2000,sr
move.l a5,-(sp)
move.l usp,a5
movem.l d0-a6,-(a5)
move.l #0,a6
move $0126(a6),d0 ; IDNestCnt
move #-1,$0126(a6) ; IDNestCnt
move #$C000,$DFF09A ; intena
move.l (sp)+,$0034(a5)
move (sp)+,-(a5)
move.l (sp)+,-(a5)
move (sp)+,d1
dc.w $F325 ; fsave -(a5)
tst.b (a5)
beq .2
moveq #-1,d2
move d2,-(a5)
and #$F000,d1
cmp #$9000,d1
bne .1
move.l (sp)+,-(a5)
move.l (sp)+,-(a5)
move.l (sp)+,-(a5)
move d1,d2
.1
dc.w $F225,$E0FF ; fmovem.x fp0-fp7,-(a5)
dc.w $F225,$BC00 ; fmovem.l fpcr/fpsr/fpiar,-(a5)
move d2,-(a5)
.2
move.l $0230(a6),a4 ; ex_LaunchPoint
move.l $0114(a6),a3 ; ThisTask
move d0,$0010(a3) ; tc_IDNestCnt
move.l a5,$0036(a3) ; tc_SPReg
moveq #$40,d0 ; TF_SWITCH
and.b $000E(a3),d0 ; tc_Flags
beq Dispatch1
move.l $0042(a3),a5 ; tc_Switch
jsr (a5)
bra Dispatch1
;------------------------------------------------------------------------------;
cnop 0,4
Dispatch0
addq.l #1,$0118(a6) ; IdleCount
or #$8000,$0124(a6)
stop #$2000
bra Dispatch2
cnop 0,4
Dispatch:
move.l $0230(a6),a4 ; ex_LaunchPoint
move #-1,$0126(a6) ; IDNestCnt
move #$C000,$DFF09A ; intena
Dispatch1
lea $0196(a6),a0 ; TaskReady
Dispatch2
move #$2700,sr
move.l (a0),a3
move.l (a3),d0
beq Dispatch0
move.l d0,(a0)
move.l d0,a1
move.l a0,$0004(a1)
move.l a3,$0114(a6) ; ThisTask
lea $0120(a6),a1
move (a1)+,(a1)+
and #$BFFF,(a1)+
move.b #2,$000F(a3) ; tc_State, TS_RUN
move $0010(a3),(a1) ; tc_IDNestCnt
tst.b (a1)
bmi Dispatch3
move #$4000,$DFF09A ; intena
Dispatch3
move #$2000,sr
addq.l #1,$011C(a6) ; DispCount
move.b $000E(a3),d2 ; tc_Flags
and #$A0,d2 ; TF_EXCEPT!TF_LAUNCH
beq Dispatch5
bpl Dispatch4
move.l $0046(a3),a5 ; tc_Launch
jsr (a5)
and #$20,d2
beq Dispatch5
Dispatch4
bsr Exception
Dispatch5
move.l $0036(a3),a5 ; tc_SPReg
jmp (a4)
;------------------------------------------------------------------------------;
cnop 0,4
Exception:
and.b #$DF,$000E(a3) ; tc_Flags, TB_EXCEPT=5
move.l $002A(a3),d1 ; tc_ExceptCode
beq Exception3
lea $0126(a6),a0 ; IDNestCnt
move #$4000,$DFF09A ; intena
lea $001A(a3),a1 ; tc_SigRecvd
move.l (a1)+,d0
and.l (a1),d0
eor.l d0,(a1)
eor.l d0,-(a1)
tst.b (a0)
bge Exception1
move #$C000,$DFF09A ; intena
Exception1
move.l $0036(a3),a1 ; tc_SPReg
move.l $000E(a3),-(a1) ; tc_Flags/tc_State/tc_IDNestCnt/tc_TDNestCnt
tst.b (a0)
bne Exception2
subq.b #1,(a0)
move #$C000,$DFF09A ; intena
Exception2
move.l #Exception4,-(a1)
move.l a1,usp
move #$0020,-(sp)
move.l d1,-(sp)
clr -(sp)
move.l $0026(a3),a1 ; tc_ExceptData
rte
cnop 0,4
Exception3
rts
cnop 0,4
Exception4
move.l #0,a6
lea Exception5(pc),a5 ; userFunction
jmp -$001E(a6) ; _LVOSupervisor
cnop 0,4
Exception5
move.l $0230(a6),a4 ; ex_LaunchPoint
addq.l #8,sp
move.l $0114(a6),a3 ; ThisTask
or.l d0,$001E(a3) ; tc_SigExcept
move.l usp,a1
move.l (a1)+,$000E(a3) ; tc_Flags/tc_State/tc_IDNestCnt/tc_TDNestCnt
move.l a1,$0036(a3) ; tc_SPReg
move $0010(a3),$0126(a6) ; IDNestCnt, tc_IDNestCnt
; tst.b $0126(a6) ; IDNestCnt
bmi Exception6
move #$4000,$DFF09A ; intena
Exception6
rts
;------------------------------------------------------------------------------;
cnop 0,4
Wait:
move.l $0114(a6),a1 ; ThisTask
move.l d0,$0016(a1) ; tc_SigWait
move #$4000,$DFF09A ; intena
and.l $001A(a1),d0 ; tc_SigRecvd
bne .2
addq.b #1,$0127(a6) ; TDNestCnt
.1
move.b #4,$000F(a1) ; tc_State, TS_WAIT
lea $01AC(a6),a0 ; TaskWait+8
move.l (a0),d0
move.l a1,(a0)
subq.l #4,a0
exg.l d0,a0
movem.l d0/a0,(a1)
move.l a1,(a0)
move.b $0126(a6),d1 ; IDNestCnt
st $0126(a6) ; IDNestCnt
move #$C000,$DFF09A ; intena
move.l a5,a0
lea -$0036(a6),a5 ; userFunction, _LVOSwitch
jsr -$001E(a6) ; _LVOSupervisor
move.l a0,a5
move #$4000,$DFF09A ; intena
move.b d1,$0126(a6) ; IDNestCnt
move.l $0016(a1),d0 ; tc_SigWait
and.l $001A(a1),d0 ; tc_SigRecvd
beq .1
subq.b #1,$0127(a6) ; TDNestCnt
.2
eor.l d0,$001A(a1) ; tc_SigRecvd
tst.b $0126(a6) ; IDNestCnt
bge .3
move #$C000,$DFF09A ; intena
.3
rts
;------------------------------------------------------------------------------;
cnop 0,4
PatchExecEnd
;------------------------------------------------------------------------------;
expansion_library dc.b 'expansion.library',0
FastExecName dc.b 'FastExec',0
dc.b '$VER: '
FastExecId dc.b 'FastExec 2.6 (21.5.97)',13,10,0
cnop 0,4
ArgArray
ArgSYSINFO dc.l 0
ArgREBOOT dc.l 0
ArgNOEXEC dc.l 0
ArgLOCAL dc.l 0
ArgPATCH dc.l 0
ArgFASTSSP dc.l 0
ArgFASTVBR dc.l 0
ArgFASTEXP dc.l 0
ArgFASTMEM dc.l 0
ArgFASTINT dc.l 0
ArgCACHE dc.l 0
ArgADDMEM dc.l 0
OldAddMemList dc.l 0
CacheBits dc.l 0
AddMemData dcb.l 260,0
FlagEBExec dc.b 0
cnop 0,4
ResEnd
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
ibrd_next = 0
ibrd_name = ibrd_next+4
ibrd_addr = ibrd_name+4
ibrd_boardaddr = ibrd_addr+4
ibrd_boardsize = ibrd_boardaddr+4
ibrd_manufact = ibrd_boardsize+4
ibrd_product = ibrd_manufact+2
ibrd_sizeof = ibrd_product+1
ilib_next = 0
ilib_name = ilib_next+4
ilib_addr = ilib_name+4
ilib_neg = ilib_addr+4
ilib_pos = ilib_neg+2
ilib_ver = ilib_pos+2
ilib_rev = ilib_ver+2
ilib_opn = ilib_rev+2
ilib_mem = ilib_opn+2
ilib_pri = ilib_mem+1
ilib_sizeof = ilib_pri+1
imem_next = 0
imem_name = imem_next+4
imem_addr = imem_name+4
imem_lower = imem_addr+4
imem_upper = imem_lower+4
imem_type = imem_upper+4
imem_pri = imem_type+2
imem_sizeof = imem_pri+1
;------------------------------------------------------------------------------;
SysInfo:
movem.l d2-d7/a2-a5,-(sp)
move.l sp,d7
lea -1024(sp),sp
move.l sp,a3
lea -68(sp),sp
move.l sp,a4
move.l a4,a2
;Kickstart
move $0014(a6),d1 ; lib_Version
move d1,(a2)+
move $0022(a6),d0
cmp #36,d1
bcc .KS
;SoftVer is zero under KS 1.3
;Use rom revision if rom version is same as exec,
;else go on with zero.
lea $01000000,a0
sub.l -$0014(a0),a0
lea $000C(a0),a0
cmp (a0)+,d1
bne .KS
move (a0),d0
.KS
move d0,(a2)+ ; SoftVer
;Workbench
moveq #-1,d0 ; ptr
bsr SetWindowPtr
move.l d0,d2
lea version_library(pc),a1 ; libName
moveq #0,d0 ; version
jsr -$0228(a6) ; _LVOOpenLibrary
exg.l d0,d2
bsr SetWindowPtr
move.l d2,d0
beq .WB
move.l d0,a1 ; library
move.l $0014(a1),d2 ; lib_Version/lib_Revision
jsr -$019E(a6) ; _LVOCloseLibrary
.WB
move.l d2,(a2)+
;ROM
lea $01000000,a0
move.l -$0014(a0),d0
sub.l d0,a0
move.l $000C(a0),(a2)+
;CPU
move $0128(a6),d1 ; AttnFlags
moveq #6,d0
tst.b d1 ; AFB_68060=7
bmi .CPU
moveq #4,d0
btst #3,d1 ; AFB_68040
bne .CPU
moveq #3,d0
btst #2,d1 ; AFB_68030
bne .CPU
moveq #2,d0
btst #1,d1 ; AFB_68020
bne .CPU
moveq #1,d0
btst #0,d1 ; AFB_68010
bne .CPU
moveq #0,d0
.CPU
move.l d0,(a2)+
;FPU
btst #3,d1 ; AFB_68040
beq .FPU40
lea StrFPU40(pc),a0
btst #6,d1
bne .FPU
.FPU40
lea Str68882(pc),a0
btst #5,d1
bne .FPU
lea Str68881(pc),a0
btst #4,d1
bne .FPU
lea StrNONE(pc),a0
.FPU
move.l a0,(a2)+
;VBR
bsr GetVBR
move.l d0,(a2)+
move.l $002A(a6),(a2)+ ; ColdCapture
move.l $002E(a6),(a2)+ ; CoolCapture
move.l $0032(a6),(a2)+ ; WarmCapture
move.l $0222(a6),(a2)+ ; KickMemPtr
move.l $0226(a6),(a2)+ ; KickTagPtr
move.l $0036(a6),(a2)+ ; SysStkUpper
move.l $003A(a6),(a2)+ ; SysStkLower
move.l $003E(a6),(a2)+ ; MaxLocMem
move.l $004E(a6),(a2)+ ; MaxExtMem
move.l $0128(a6),(a2)+ ; AttnFlags
lea .FmtMisc(pc),a0 ; formatString
move.l a4,a1 ; dataStream
lea PutChProc(pc),a2 ; putChProc
; move.l #0,a3 ; putChData
jsr -$020A(a6) ; _LVORawDoFmt
move.l a3,a0 ; string
bsr Put
move.l d7,sp
movem.l (sp)+,d2-d7/a2-a5
tst.l d0
beq .Rts
bsr PutLF
bsr SysIBrd
tst.l d0
beq .Rts
bsr PutLF
bsr SysIMem
tst.l d0
beq .Rts
bsr PutLF
move #$017A,d0 ; LibList
bsr SysIList
tst.l d0
beq .Rts
bsr PutLF
move #$015E,d0 ; DeviceList
bsr SysIList
tst.l d0
beq .Rts
bsr PutLF
move #$0150,d0 ; ResourceList
bsr SysIList
tst.l d0
beq .Rts
bsr PutLF
bsr SysIRes
.Rts
rts
.FmtMisc
dc.b 'Kickstart: %d.%d',10
dc.b 'Workbench: %d.%d',10
dc.b 'ROM: %d.%d',10
dc.b 'CPU: 680%ld0',10
dc.b 'FPU: %s',10
dc.b 'VBR: $%08lx',10
dc.b 'ColdCapture: $%08lx',10
dc.b 'CoolCapture: $%08lx',10
dc.b 'WarmCapture: $%08lx',10
dc.b 'KickMemPtr: $%08lx',10
dc.b 'KickTagPtr: $%08lx',10
dc.b 'SysStkUpper: $%08lx',10
dc.b 'SysStkLower: $%08lx',10
dc.b 'MaxLocMem: $%08lx',10
dc.b 'MaxExtMem: $%08lx',10
dc.b 'AttnFlags: $%08lx',10
dc.b 0
cnop 0,2
;------------------------------------------------------------------------------;
SysIBrd:
movem.l d2-d4/a2-a4,-(sp)
lea -80(sp),sp
move.l sp,a3
lea .Str(pc),a0 ; string
moveq #1,d0
bsr PutS
move.l d0,d4
beq .Done
bsr GetIBrd
move.l d0,d2
beq .Done
move.l d0,d1
addq.l #1,d1
beq .Err
.Loop
move.l d0,a4
move.l sp,d3
moveq #0,d0
move.b ibrd_product(a4),d0
move.l d0,-(sp)
move ibrd_manufact(a4),d0
move.l d0,-(sp)
move.l ibrd_boardsize(a4),-(sp)
move.l ibrd_boardaddr(a4),-(sp)
move.l ibrd_addr(a4),-(sp)
lea .Fmt(pc),a0 ; formatString
move.l sp,a1 ; dataStream
lea PutChProc(pc),a2 ; putChProc
; lea #0,a3 ; putChData
jsr -$020A(a6) ; _LVORawDoFmt
move.l a3,a0 ; string
moveq #1,d0
bsr PutS
move.l d3,sp
move.l d0,d4
beq .Quit
move.l (a4),d0 ; ilib_next
bne .Loop
moveq #1,d4
.Quit
move.l d2,a0 ; info
bsr FreeInfo
.Done
move.l d4,d0
lea 80(sp),sp
movem.l (sp)+,d2-d4/a2-a4
rts
.Err
lea TxtAllocMem(pc),a0 ; string
bsr PutS
moveq #0,d4
bra .Done
.Str
dc.b 'BOARDS:',10
dc.b 'Address BoardAddr BoardSize Manufacturer Product',10,0
.Fmt
dc.b '$%08lx $%08lx $%08lx %12ld %7ld',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIList:
movem.l d2-d5/a2-a4,-(sp)
lea -80(sp),sp
move.l sp,a3
move.l d0,d5
lea .Str150(pc),a0 ; string
cmp #$0150,d0
beq .Header
lea .Str15E(pc),a0 ; string
cmp #$015E,d0
beq .Header
lea .Str17A(pc),a0 ; string
.Header
bsr PutS
move.l d0,d4
beq .Done
lea .Str(pc),a0 ; string
moveq #1,d0
bsr PutS
move.l d0,d4
beq .Done
move d5,d0
bsr GetIList
move.l d0,d2
beq .Done
move.l d0,d1
addq.l #1,d1
beq .Err
.Loop
move.l d0,a4
move.l sp,d3
moveq #0,d0
move ilib_opn(a4),d0
move.l d0,-(sp)
move ilib_rev(a4),d0
move.l d0,-(sp)
move ilib_ver(a4),d0
move.l d0,-(sp)
move ilib_pos(a4),d0
move.l d0,-(sp)
move ilib_neg(a4),d0
move.l d0,-(sp)
move.b ilib_pri(a4),d0
ext d0
ext.l d0
move.l d0,-(sp)
moveq #0,d0
move.b ilib_mem(a4),d0
bsr GetMemStr
move.l d0,-(sp)
move.l ilib_name(a4),-(sp)
move.l ilib_addr(a4),-(sp)
lea .Fmt(pc),a0 ; formatString
move.l sp,a1 ; dataStream
lea PutChProc(pc),a2 ; putChProc
; lea #0,a3 ; putChData
jsr -$020A(a6) ; _LVORawDoFmt
move.l a3,a0 ; string
moveq #1,d0
bsr PutS
move.l d3,sp
move.l d0,d4
beq .Quit
move.l (a4),d0 ; ilib_next
bne .Loop
moveq #1,d4
.Quit
move.l d2,a0 ; info
bsr FreeInfo
.Done
move.l d4,d0
lea 80(sp),sp
movem.l (sp)+,d2-d5/a2-a4
rts
.Err
lea TxtAllocMem(pc),a0 ; string
bsr PutS
moveq #0,d4
bra .Done
.Str150
dc.b 'RESOURCES:',10,0
.Str15E
dc.b 'DEVICES:',10,0
.Str17A
dc.b 'LIBRARIES:',10,0
.Str
dc.b 'Address Name MemType Pri Neg Pos Version OpenCnt',10,0
.Fmt
dc.b '$%08lx %-20.20s %.4s %4ld %5ld %5ld %5ld.%-5ld %5ld',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIMem:
movem.l d2-d4/a2-a4,-(sp)
lea -80(sp),sp
move.l sp,a3
lea .Str(pc),a0 ; string
moveq #1,d0
bsr PutS
move.l d0,d4
beq .Done
bsr GetIMem
move.l d0,d2
beq .Done
move.l d0,d1
addq.l #1,d1
beq .Err
.Loop
move.l d0,a4
move.l sp,d3
move.b imem_pri(a4),d0
ext d0
ext.l d0
move.l d0,-(sp)
moveq #0,d0
move imem_type(a4),d0
move.l d0,-(sp)
move.l imem_upper(a4),-(sp)
move.l imem_lower(a4),-(sp)
move.l imem_name(a4),-(sp)
move.l imem_addr(a4),-(sp)
lea .Fmt(pc),a0 ; formatString
move.l sp,a1 ; dataStream
lea PutChProc(pc),a2 ; putChProc
; lea #0,a3 ; putChData
jsr -$020A(a6) ; _LVORawDoFmt
move.l a3,a0 ; string
moveq #1,d0
bsr PutS
move.l d3,sp
move.l d0,d4
beq .Quit
move.l (a4),d0 ; ilib_next
bne .Loop
moveq #1,d4
.Quit
move.l d2,a0 ; info
bsr FreeInfo
.Done
move.l d4,d0
lea 80(sp),sp
movem.l (sp)+,d2-d4/a2-a4
rts
.Err
lea TxtAllocMem(pc),a0 ; string
bsr PutS
moveq #0,d4
bra .Done
.Str
dc.b 'MEMORY HEADERS:',10
dc.b 'Address Name Lower Upper Type Pri',10,0
.Fmt
dc.b '$%08lx %-20.20s $%08lx $%08lx $%04lx %4ld',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIRes:
movem.l d2-d4/a2-a4,-(sp)
lea -80(sp),sp
move.l sp,a3
lea -20(sp),sp
move.l sp,d4
lea .Str(pc),a0 ; string
moveq #1,d0
bsr PutS
tst.l d0
beq .End
move.l $012C(a6),a2 ; ResModules
.Loop
move.l (a2)+,d0
beq .Ok
bgt .Put
bclr #31,d0
move.l d0,a2
bra .Loop
.Put
move.l d0,a4
move.l sp,d3
move.b $000D(a4),d0 ; rt_Pri
ext d0
ext.l d0
move.l d0,-(sp)
move.b $000C(a4),d0 ; rt_Type
bsr GetTypeString
move.l d0,-(sp)
move.b $000B(a4),d0 ; rt_Version
ext d0
ext.l d0
move.l d0,-(sp)
moveq #0,d0
move.b $000A(a4),d0 ; rt_Flags
move.l d0,-(sp)
move.l $000E(a4),a0 ; rt_Name
move.l d4,a1
.Loop2
move.b (a0)+,d0
beq .Ok2
cmp.b #10,d0
beq .Ok2
cmp.b #13,d0
beq .Ok2
move.b d0,(a1)+
bra .Loop2
.Ok2
clr.b (a1)
move.l d4,-(sp)
move.l a4,-(sp)
lea .Fmt(pc),a0 ; formatString
move.l sp,a1 ; dataStream
move.l a2,-(sp)
lea PutChProc(pc),a2 ; putChProc
; lea #0,a3 ; putChData
jsr -$020A(a6) ; _LVORawDoFmt
move.l (sp)+,a2
move.l a3,a0 ; string
moveq #1,d0
bsr PutS
move.l d3,sp
tst.l d0
bne .Loop
bra .End
.Ok
moveq #1,d0
.End
lea 100(sp),sp
movem.l (sp)+,d2-d4/a2-a4
rts
.Str
dc.b 'RESIDENTS:',10
dc.b 'Address Name Flags Vers Type Pri',10,0
.Fmt
dc.b '$%08lx %-20.20s $%02lx %4ld %-12s %4ld',10,0
cnop 0,2
;------------------------------------------------------------------------------;
FreeInfo:
; a0=info
move.l a2,-(sp)
move.l a0,d0
beq .End
.Loop
move.l d0,a2
move.l 4(a2),a1 ; memoryBlock
bsr OSFreeVec
move.l a2,a1 ; memoryBlock
move.l (a1),a2
bsr OSFreeVec
move.l a2,d0
bne .Loop
.End
move.l (sp)+,a2
rts
;------------------------------------------------------------------------------;
GetIBrd:
movem.l d2/a2/a3,-(sp)
moveq #0,d2
sub.l a2,a2
.Loop
move.l a2,a0 ; oldConfigDev
moveq #-1,d0 ; manufacturer
moveq #-1,d1 ; product
move.l a6,-(sp)
move.l _ExpansionBase(a5),a6
jsr -$0048(a6) ; _LVOFindConfigDev
move.l (sp)+,a6
tst.l d0
beq .Ok
move.l d0,a2
moveq #ibrd_sizeof,d0 ; byteSize
moveq #0,d1 ; requirements, MEMF_ANY
bsr OSAllocVec
tst.l d0
beq .Err
tst.l d2
bne .Ok2
move.l d0,d2
bra .Ok3
.Ok2
move.l d0,(a3) ; ibrd_next
.Ok3
move.l d0,a3
clr.l (a3) ; ibrd_next
clr.l ibrd_name(a3)
move.l a2,ibrd_addr(a3)
move.l $0020(a2),ibrd_boardaddr(a3); cd_BoardAddr
move.l $0024(a2),ibrd_boardsize(a3); cd_BoardSize
move $0014(a2),ibrd_manufact(a3)
move.b $0011(a2),ibrd_product(a3)
bra .Loop
.Err
move.l d2,a0
bsr FreeInfo
moveq #-1,d2
.Ok
move.l d2,d0
movem.l (sp)+,d2/a2/a3
rts
;------------------------------------------------------------------------------;
GetIList:
movem.l d2/a2/a3,-(sp)
moveq #0,d2
lea (a6,d0),a2
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),a2
tst.l (a2)
beq .Ok
moveq #ilib_sizeof,d0 ; byteSize
moveq #0,d1 ; requirements, MEMF_ANY
bsr OSAllocVec
tst.l d0
beq .Err
tst.l d2
bne .Ok2
move.l d0,d2
bra .Ok3
.Ok2
move.l d0,(a3) ; ilib_next
.Ok3
move.l d0,a3
clr.l (a3) ; ilib_next
move.l a2,ilib_addr(a3)
move.l $0010(a2),ilib_neg(a3) ; lib_NegSize/lib_PosSize
move.l $0014(a2),ilib_ver(a3) ; lib_Revision/lib_Version
move $0020(a2),ilib_opn(a3) ; lib_OpenCnt
move.l a2,a1 ; address
bsr MyTypeOfMem
move.b d0,ilib_mem(a3)
move.b $0009(a2),ilib_pri(a3) ; ln_Pri
move.l a2,a0
bsr GetIName
move.l d0,ilib_name(a3)
beq .Loop
addq.l #1,d0
bne .Loop
.Err
jsr -$008A(a6) ; _LVOPermit
move.l d2,a0
bsr FreeInfo
moveq #-1,d2
bra .Done
.Ok
jsr -$008A(a6) ; _LVOPermit
.Done
move.l d2,d0
movem.l (sp)+,d2/a2/a3
rts
;------------------------------------------------------------------------------;
GetIMem:
movem.l d2/a2/a3,-(sp)
moveq #0,d2
lea $0142(a6),a2 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),a2
tst.l (a2)
beq .Ok
moveq #imem_sizeof,d0 ; byteSize
moveq #0,d1 ; requirements, MEMF_ANY
bsr OSAllocVec
tst.l d0
beq .Err
tst.l d2
bne .Ok2
move.l d0,d2
bra .Ok3
.Ok2
move.l d0,(a3) ; imem_next
.Ok3
move.l d0,a3
clr.l (a3) ; imem_next
move.l a2,imem_addr(a3)
move.l $0014(a2),imem_lower(a3); mh_Lower
move.l $0018(a2),imem_upper(a3); mh_Upper
move $000E(a2),imem_type(a3) ; mh_Attributes
move.b $0009(a2),imem_pri(a3) ; ln_Pri
move.l a2,a0
bsr GetIName
move.l d0,imem_name(a3)
beq .Loop
addq.l #1,d0
bne .Loop
.Err
jsr -$008A(a6) ; _LVOPermit
move.l d2,a0
bsr FreeInfo
moveq #-1,d2
bra .Done
.Ok
jsr -$008A(a6) ; _LVOPermit
.Done
move.l d2,d0
movem.l (sp)+,d2/a2/a3
rts
;------------------------------------------------------------------------------;
GetIName:
; a0=node
move.l a2,-(sp)
move.l a0,a2
move.l $000A(a2),d0 ; ln_Name
beq .End
move.l d0,a0 ; string
bsr StrLen
tst.l d0
beq .End
addq.l #1,d0 ; byteSize
moveq #1,d1 ; requirements, MEMF_PUBLIC
bsr OSAllocVec
tst.l d0
beq .Err
move.l $000A(a2),a0 ; string, ln_Name
move.l d0,a1 ; dest
move.l d0,a2
bsr StrCpy
move.l a2,d0
.End
move.l (sp)+,a2
rts
.Err
moveq #-1,d0
bra .End
;------------------------------------------------------------------------------;
GetMemStr:
lea Strfast(pc),a0
btst #2,d0
bne .Ok
lea Strchip(pc),a0
btst #1,d0
bne .Ok
lea Strslow(pc),a0
btst #0,d0
bne .Ok
lea Strchip(pc),a0
.Ok
move.l a0,d0
rts
;------------------------------------------------------------------------------;
GetTypeString:
; d0=type
lea Strunknown(pc),a0
tst.b d0
beq .Ok
lea Strtask(pc),a0
subq.b #1,d0
beq .Ok
lea Strinterrupt(pc),a0
subq.b #1,d0
beq .Ok
lea Strdevice(pc),a0
subq.b #1,d0
beq .Ok
lea Strmsgport(pc),a0
subq.b #1,d0
beq .Ok
lea Strmessage(pc),a0
subq.b #1,d0
beq .Ok
lea Strfreemsg(pc),a0
subq.b #1,d0
beq .Ok
lea Strreplymsg(pc),a0
subq.b #1,d0
beq .Ok
lea Strresource(pc),a0
subq.b #1,d0
beq .Ok
lea Strlibrary(pc),a0
subq.b #1,d0
beq .Ok
lea Strmemory(pc),a0
subq.b #1,d0
beq .Ok
lea Strsoftint(pc),a0
subq.b #1,d0
beq .Ok
lea Strfont(pc),a0
subq.b #1,d0
beq .Ok
lea Strprocess(pc),a0
subq.b #1,d0
beq .Ok
lea Strsemaphore(pc),a0
subq.b #1,d0
beq .Ok
lea Strsignalsem(pc),a0
subq.b #1,d0
beq .Ok
lea Strbootnode(pc),a0
subq.b #1,d0
beq .Ok
lea Strkickmem(pc),a0
subq.b #1,d0
beq .Ok
lea Strgraphics(pc),a0
subq.b #1,d0
beq .Ok
lea Strdeathmessage(pc),a0
subq.b #1,d0
beq .Ok
sub.l a0,a0
.Ok
move.l a0,d0
rts
;------------------------------------------------------------------------------;
Usage:
lea TxtUsage(pc),a0 ; string
moveq #0,d0
bsr PutS
bra Quit
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
AddResident:
; out d0=output from MakeResident()
; -2=FindResident("expansion.library") failed.
movem.l d2-d4/a2,-(sp)
lea expansion_library(pc),a1; name
jsr -$0060(a6) ; _LVOFindResident
tst.l d0
beq .Err
move.l d0,a0
move.b $000D(a0),d4 ; pri, rt_Pri
moveq #0,d0
addq.b #1,d4
lea Resident(pc),a0 ; code
lea FastExecName(pc),a1 ; name
lea FastExecId(pc),a2 ; idString
move.l #ResEnd-Resident,d0 ; size
moveq #1,d1 ; flags, RTF_COLDSTART
moveq #2,d2 ; version
moveq #0,d3 ; type
bsr MakeResident
.End
movem.l (sp)+,d2-d4/a2
rts
.Err
moveq #-2,d0
bra .End
;------------------------------------------------------------------------------;
;ASCII To Integer
AToI:
move.l d2,a1
moveq #0,d0
moveq #0,d1
.Loop
move.b (a0)+,d1
sub.b #'0',d1
cmp.b #9,d1
bhi .Quit
add.l d0,d0
move.l d0,d2
lsl.l #2,d0
add.l d2,d0
add.l d1,d0
bra .Loop
.Quit
move.l a1,d2
rts
;------------------------------------------------------------------------------;
FindArg:
; a0=args
; a1=arg
movem.l a2/a3,-(sp)
move.l a0,a2
move.l a1,a3
.Loop
move.l (a2)+,d0
beq .Quit
move.l d0,a0
move.l a3,a1
bsr OSStricmp
tst.l d0
bne .Loop
move.l (a2),d0
bne .Quit
moveq #1,d0
.Quit
movem.l (sp)+,a2/a3
rts
;------------------------------------------------------------------------------;
FindKickTag:
; a1=name
movem.l a2/a3,-(sp)
move.l a1,a3
move.l $0226(a6),d0 ; KickTagPtr
beq .End
move.l d0,a2
.Loop
move.l (a2)+,d0
beq .End
bpl .Ok
bclr #31,d0
move.l d0,a2
bra .Loop
.Ok
move.l d0,a0
move.l $000E(a0),d0 ; rt_Name
beq .Loop
move.l d0,a0 ; string1
move.l a3,a1 ; string2
bsr StrCmp
tst.l d0
bne .Loop
move.l a2,d0
.End
movem.l (sp)+,a2/a3
rts
;------------------------------------------------------------------------------;
GetArgs:
; a0=dosCmdBuf
; out d0=args
movem.l d2/a2,-(sp)
clr.l -(sp)
.Loop1
move.b (a0)+,d0
cmp.b #10,d0
beq .Quit
cmp.b #';',d0
beq .Quit
cmp.b #' ',d0
beq .Loop1
cmp.b #9,d0
beq .Loop1
cmp.b #'"',d0
beq .Quot
subq.l #1,a0
move.l a0,-(sp)
.Loop2
move.b (a0)+,d0
cmp.b #10,d0
beq .Quit
cmp.b #';',d0
beq .Quit
cmp.b #' ',d0
beq .Next2
cmp.b #9,d0
beq .Next2
cmp.b #'=',d0
bne .Loop2
.Next2
clr.b -1(a0)
bra .Loop1
.Quot
move.l a0,-(sp)
.Loop3
move.b (a0)+,d0
cmp.b #10,d0
beq .Quit
cmp.b #'"',d0
bne .Loop3
clr.b -1(a0)
bra .Loop1
.Quit
clr.b -(a0)
move.l sp,a2
.Size
tst.l (a2)+
bne .Size
move.l a2,d0 ; byteSize
sub.l sp,d0
move.l d0,d2
moveq #0,d1 ; requirements, MEMF_ANY
bsr OSAllocVec
move.l d0,a0
move.l a2,a1
subq.l #4,a1
subq.l #4,d2
lsr.l #2,d2
bra .Next
.Copy
move.l -(a1),(a0)+
.Next
dbf d2,.Copy
clr.l (a0)
move.l a2,sp
movem.l (sp)+,d2/a2
rts
;------------------------------------------------------------------------------;
;Hex To Integer
HToI:
moveq #0,d0
moveq #0,d1
.Loop
move.b (a0)+,d1
cmp.b #'0',d1
bcs .Rts
cmp.b #'9',d1
bhi .2
sub.b #'0',d1
bra .Next
.2
cmp.b #'A',d1
bcs .Rts
cmp.b #'F',d1
bhi .3
sub.b #$37,d1
bra .Next
.3
cmp.b #'a',d1
bcs .Rts
cmp.b #'f',d1
bhi .Rts
sub.b #$57,d1
; bra .Next
.Next
lsl.l #4,d0
add.l d1,d0
bra .Loop
.Rts
rts
;------------------------------------------------------------------------------;
MakeResident:
; a0=code
; a1=name
; a2=idString
; d0=size
; d1=flags
; d2=version
; d3=type
; d4=pri
; out d0=-1:already installed, 0:out of memory, 1:okay
movem.l d2-d7/a2-a4,-(sp)
move.b d1,d7
lsl.l #8,d7
move.b d2,d7
lsl.l #8,d7
move.b d3,d7
lsl.l #8,d7
move.b d4,d7
move.l a2,d4
move.l a1,d3
move.l a0,d2
move.l d0,d6
; move.l #0,a1 ; name
bsr FindKickTag
tst.l d0
bne .Err
moveq #$003A,d0 ; sizeof(MemList)+8+sizeof(Resident)
add.l d6,d0 ; byteSize
move.l #$00050401,d1 ; requirements, MEMF_PUBLIC!MEMF_KICK!MEMF_CLEAR!MEMF_REVERSE
bsr OSAllocMem
tst.l d0
beq .End
move.l d0,a2
lea $0020(a2),a3 ; sizeof(MemList)+8
lea $001A(a3),a4 ; sizeof(Resident)
move.l d2,a0 ; source
move.l a4,a1 ; dest
move.l d6,d0 ; size
jsr -$0276(a6) ; _LVOCopyMemQuick
move #$4AFC,(a3) ; rt_MatchWord
move.l a3,$0002(a3) ; rt_MatchTag
lea (a4,d6.l),a0
move.l a0,$0006(a3) ; rt_EndSkip
move.l d7,$000A(a3) ; rt_Flags/rt_Version/rt_Type/rt_Pri
move.l d3,d0
beq .Name
sub.l d2,d0
add.l a4,d0
.Name
move.l d0,$000E(a3) ; rt_Name
move.l d4,d0
beq .ID
sub.l d2,d0
add.l a4,d0
.ID
move.l d0,$0012(a3) ; rt_IdString
move.l a4,$0016(a3) ; rt_Init
jsr -$0084(a6) ; _LVOForbid
moveq #0,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
move.l d0,-(sp)
move.l a2,a0 ; ptr
moveq #$003A,d0 ; sizeof(MemList)+8+sizeof(Resident)
add.l d6,d0 ; size
bsr SetKickMemPtr
lea $0018(a2),a0 ; ptr, sizeof(MemList)
move.l a3,(a0)
clr.l 4(a0)
bsr SetKickTagPtr
move.l (sp)+,d0 ; cacheBits
moveq #-1,d1 ; cacheMask
bsr OSCacheControl
jsr -$008A(a6) ; _LVOPermit
moveq #1,d0
.End
movem.l (sp)+,d2-d7/a2-a4
rts
.Err
moveq #-1,d0
bra .End
;------------------------------------------------------------------------------;
cnop 0,4
OSAllocMem:
cmp #39,$0014(a6) ; lib_Version
bcs .Old
.OS
jmp -$00C6(a6) ; _LVOAllocMem
.Old
bclr #10,d1 ; MEMB_KICK
beq .OS
or #$0002,d1 ; MEMF_CHIP
btst #18,d1 ; MEMB_REVERSE
beq .OS
movem.l d2/d3,-(sp)
move.l d0,d3
beq .End
move.l d1,d2
lea $0142(a6),a0 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a0),a0 ; mc_Next
tst.l (a0) ; mc_Next
beq .Err
move $000E(a0),d0 ; mh_Attributes
and d2,d0
cmp d2,d0
bne .Loop
cmp.l $001C(a0),d3 ; mh_Free
bhi .Loop
btst #18,d2 ; MEMB_REVERSE
bne .Reverse
; move.l #0,a0 ; freeList
move.l d3,d0 ; byteSize
jsr -$00BA(a6) ; _LVOAllocate
tst.l d0
beq .Loop
.Quit
jsr -$008A(a6) ; _LVOPermit
btst #16,d2 ; MEMB_CLEAR
beq .End
moveq #0,d1
move.l d0,a0
addq.l #7,d3
lsr.l #3,d3
move d3,d2
swap d3
bra .Next
.Clear
move.l d1,(a0)+
move.l d1,(a0)+
.Next
dbf d2,.Clear
dbf d3,.Clear
.End
movem.l (sp)+,d2/d3
rts
.Err
jsr -$008A(a6) ; _LVOPermit
moveq #0,d0
bra .End
.Reverse
moveq #0,d1
move.l $0010(a0),d0 ; mh_First
beq .Loop
.Loop2
move.l d0,a1
cmp.l $0004(a1),d3 ; mc_Next
bhi .Ok2
move.l a1,d1
.Ok2
move.l (a1),d0 ; mc_Next
bne .Loop2
tst.l d1
beq .Loop
move.l d1,a1
move.l $0004(a1),d0 ; mc_Bytes
sub.l d3,d0
and #-8,d0
add.l d0,a1 ; location
move.l d3,d0 ; byteSize
jsr -$00CC(a6) ; _LVOAllocAbs
bra .Quit
;------------------------------------------------------------------------------;
cnop 0,4
OSAllocVec:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
jmp -$02AC(a6) ; _LVOAllocVec
.Old
tst.l d0
beq .Rts
addq.l #4,d0 ; byteSize
move.l d0,-(sp)
jsr -$00C6(a6) ; _LVOAllocMem
move.l (sp)+,d1
tst.l d0
beq .Rts
move.l d0,a0
move.l d1,(a0)+
move.l a0,d0
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSCheckSignal:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
move.l a6,-(sp)
move.l _DOSBase(a5),a6
jsr -$0318(a6) ; _LVOCheckSignal
move.l (sp)+,a6
rts
.Old
move.l d1,-(sp)
moveq #0,d0 ; newSignals
jsr -$0132(a6) ; _LVOSetSignal
and.l (sp)+,d0
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSCloseLibrary:
move.l a1,d0
beq .Rts
jmp -$019E(a6) ; _LVOCloseLibrary
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSColdReboot:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
jmp -$02D6(a6) ; _LVOColdReboot
.Old
lea .Func(pc),a5 ; userFunction
jsr -$001E(a6) ; _LVOSupervisor
cnop 0,4
.Func
lea $01000000,a0
sub.l -$0014(a0),a0
move.l $0004(a0),a0
subq.l #2,a0
reset
jmp (a0)
;------------------------------------------------------------------------------;
cnop 0,4
OSFreeArgs:
cmp #36,$0014(a6) ; lib_Version
bcs .Rts
move.l a6,-(sp)
move.l _DOSBase(a5),a6
jsr -$035A(a6) ; _LVOFreeArgs
move.l (sp)+,a6
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSFreeVec:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
jmp -$02B2(a6) ; _LVOFreeVec
.Old
move.l a1,d0
beq .Rts
move.l -(a1),d0 ; byteSize
jmp -$00D2(a6) ; _LVOFreeMem
.Rts
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSPutStr:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
move.l a6,-(sp)
move.l _DOSBase(a5),a6
jsr -$03B4(a6) ; _LVOPutStr
move.l (sp)+,a6
rts
.Old
movem.l d2/d3/a6,-(sp)
move.l _DOSBase(a5),a6
move.l d1,d2 ; buffer
beq .Quit
move.l d2,a0 ; cstr
bsr StrLen
move.l d0,d3 ; length
beq .Quit
jsr -$003C(a6) ; _LVOOutput
move.l d0,d1 ; file
beq .Quit
jsr -$0030(a6) ; _LVOWrite
.Quit
moveq #0,d0
movem.l (sp)+,d2/d3/a6
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSStricmp:
cmp #37,$0014(a6) ; lib_Version
bcs .Old
move.l a6,-(sp)
move.l _UtilityBase(a5),a6
jsr -$00A2(a6) ; _LVOStricmp
move.l (sp)+,a6
rts
.Old
movem.l d2/a2/a3,-(sp)
move.l a0,a2
move.l a1,a3
.Loop
move.b (a2)+,d0
beq .End0
bsr OSToUpper
move.b d0,d2
move.b (a3)+,d0
beq .End1
bsr OSToUpper
cmp.b d0,d2
beq .Loop
bcc .End1
.End2
moveq #-1,d0
bra .Quit
.End1
moveq #1,d0
bra .Quit
.End0
tst.b (a3)
bne .End2
moveq #0,d0
.Quit
movem.l (sp)+,d2/a2/a3
rts
;------------------------------------------------------------------------------;
cnop 0,4
OSToUpper:
cmp #37,$0014(a6) ; lib_Version
bcs .Old
move.l a6,-(sp)
move.l _UtilityBase(a5),a6
jsr -$00AE(a6) ; _LVOToUpper
move.l (sp)+,a6
rts
.Old
and.l #$FF,d0
cmp #'a',d0
bcs.s .Rts
cmp #'z',d0
bls.s .Ok
cmp #'à',d0
bcs.s .Rts
cmp #'÷',d0
beq.s .Rts
cmp #'þ',d0
bhi.s .Rts
.Ok
sub #32,d0
.Rts
rts
;------------------------------------------------------------------------------;
Put:
; a0=buffer
movem.l d2/a2,-(sp)
move.l a0,a2
.Loop
move.l a2,a0 ; string
.Loop2
cmp.b #10,(a2)+
bne .Loop2
move.b (a2),d2
clr.b (a2)
moveq #1,d0
bsr PutS
move.b d2,(a2)
tst.l d0
beq .End
tst.b d2
bne .Loop
moveq #1,d0
.End
movem.l (sp)+,d2/a2
rts
;------------------------------------------------------------------------------;
PutChProc:
move.b d0,(a3)+
rts
;------------------------------------------------------------------------------;
PutLF:
pea $0A000000
move.l sp,d1 ; str
bsr OSPutStr
addq.l #4,sp
rts
;------------------------------------------------------------------------------;
PutS:
; a0=string
; d0=check ctrl-c
; out d0=1:continue/0:break
tst.l d0
beq .Ok
moveq #1,d1 ; mask
ror #4,d1 ; SIGBREAKF_CTRL_C
move.l a0,-(sp)
bsr OSCheckSignal
move.l (sp)+,a0
tst.l d0
bne .Err
.Ok
move.l a0,d1 ; str
bsr OSPutStr
moveq #1,d0
rts
.Err
lea .Str(pc),a0
move.l a0,d1 ; str
bsr OSPutStr
moveq #0,d0
rts
.Str
dc.b '***Break',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SetKickMemPtr:
; a0=ptr
; d0=size
lea $000E(a0),a1 ; ml_NumEntries
move #1,(a1)+
move.l a0,(a1)+
move.l d0,(a1)
move.l $0222(a6),(a0) ; KickMemPtr
move.l a0,$0222(a6) ; KickMemPtr
jsr -$0264(a6) ; _LVOSumKickData
move.l d0,$022A(a6) ; KickCheckSum
bra OSCacheClearU
;------------------------------------------------------------------------------;
SetKickTagPtr:
; a0=ptr
move.l a0,a1
.Loop
move.l (a1)+,d0
beq .Ok
bpl .Loop
bclr #31,d0
move.l d0,a1
bra .Loop
.Ok
subq.l #4,a1
move.l $0226(a6),d0 ; KickTagPtr
beq .Tag
bset #31,d0
move.l d0,(a1)
.Tag
move.l a0,$0226(a6) ; KickTagPtr
jsr -$0264(a6) ; _LVOSumKickData
move.l d0,$022A(a6) ; KickCheckSum
bra OSCacheClearU
;------------------------------------------------------------------------------;
SetWindowPtr:
; d0=ptr
; out d0=old ptr
move.l d0,-(sp)
sub.l a1,a1 ; name
jsr -$0126(a6) ; _LVOFindTask
move.l d0,a0
move.l $00B8(a0),d0 ; pr_WindowPtr
move.l (sp)+,$00B8(a0) ; pr_WindowPtr
rts
;------------------------------------------------------------------------------;
StrCpy:
; a0=string
; a1=dest
move.b (a0)+,(a1)+
bne StrCpy
rts
;------------------------------------------------------------------------------;
StrLen:
; a0=string
; out d0=length
move.l a0,d0
addq.l #1,d0
.Loop
tst.b (a0)+
bne .Loop
sub.l d0,a0
move.l a0,d0
rts
;------------------------------------------------------------------------------;
StrCmp:
; a0=string1
; a1=string2
move.b (a0)+,d0
beq .End0
move.b (a1)+,d1
beq .End1
cmp.b d0,d1
beq StrCmp
bcc .End1
.End2
moveq #-1,d0
rts
.End1
moveq #1,d0
rts
.End0
tst.b (a1)+
bne .End2
moveq #0,d0
rts
;------------------------------------------------------------------------------;
XToI:
cmp.b #'$',(a0)
beq .H
; cmp.b #'%',(a0)
; beq .B
cmp.b #'0',(a0)
bne AToI
addq.l #1,a0
cmp.b #'x',(a0)
beq .H
cmp.b #'X',(a0)
bne AToI
.H
addq.l #1,a0
bra HToI
;.B
; addq.l #1,a0
; bra BToI
;------------------------------------------------------------------------------;
XToIS:
cmp.b #'+',(a0)+
beq XToI
cmp.b #'-',-(a0)
bne XToI
addq.l #1,a0
bsr XToI
neg.l d0
rts
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
dos_library dc.b 'dos.library',0
utility_library dc.b 'utility.library',0
version_library dc.b 'version.library',0
TxtAllocMem
dc.b 'FastExec: Out of memory',10,0
TxtExpansion
dc.b 'FastExec: Can''t find expansion.library in ResModules list',10,0
TxtExec
dc.b 'FastExec: exec.library is already in fast memory - you don''t need this program',10,0
TxtAddMem
dc.b 'FastExec: Bad arguments for ADDMEM option',10,0
Strchip dc.b 'chip',0
Strfast dc.b 'fast',0
Strslow dc.b 'slow',0
Strunknown dc.b 'unknown',0
Strtask dc.b 'task',0
Strinterrupt dc.b 'interrupt',0
Strdevice dc.b 'device',0
Strmsgport dc.b 'msgport',0
Strmessage dc.b 'message',0
Strfreemsg dc.b 'freemsg',0
Strreplymsg dc.b 'replymsg',0
Strresource dc.b 'resource',0
Strlibrary dc.b 'library',0
Strmemory dc.b 'memory',0
Strsoftint dc.b 'softint',0
Strfont dc.b 'font',0
Strprocess dc.b 'process',0
Strsemaphore dc.b 'semaphore',0
Strsignalsem dc.b 'signalsem',0
Strbootnode dc.b 'bootnode',0
Strkickmem dc.b 'kickmem',0
Strgraphics dc.b 'graphics',0
Strdeathmessage dc.b 'deathmessage',0
Str68881 dc.b '68881',0
Str68882 dc.b '68882',0
StrFPU40 dc.b '68040 FPU',0
StrNONE dc.b 'none',0
StrSYSINFO dc.b 'SYSINFO',0
StrREBOOT dc.b 'REBOOT',0
StrNOEXEC dc.b 'NOEXEC',0
StrLOCAL dc.b 'LOCAL',0
StrFASTSSP dc.b 'FASTSSP',0
StrFASTVBR dc.b 'FASTVBR',0
StrFASTEXP dc.b 'FASTEXP',0
StrFASTMEM dc.b 'FASTMEM',0
StrFASTINT dc.b 'FASTINT',0
StrCACHE dc.b 'CACHE',0
StrPATCH dc.b 'PATCH',0
StrADDMEM dc.b 'ADDMEM',0
;------------------------------------------------------------------------------;
Template
dc.b 'SYSINFO/S,REBOOT/S,NOEXEC/S,LOCAL/S,PATCH/S,FASTSSP/S,FASTVBR/S,FASTEXP/S,FASTMEM/S,FASTINT/S,CACHE/K,ADDMEM/K/M',0
;------------------------------------------------------------------------------;
TxtUsage
dc.b 'FastExec 2.6 (21.5.97)',10
dc.b 'Torbjörn A. Andersson.',10
dc.b 'Public Domain.',10
dc.b 10
dc.b 'Usage: FastExec [SYSINFO] [REBOOT] [NOEXEC] [LOCAL] [PATCH]',10
dc.b ' [FASTSSP] [FASTVBR] [FASTEXP] [FASTMEM] [FASTINT]',10
dc.b ' [CACHE 0xhhhhhhhh]',10
dc.b ' [ADDMEM <base size attr pri> ...]',10
dc.b 0
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
END
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;