home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
The Best of Mecomp Multimedia 1
/
Mecomp-CD.iso
/
amiga
/
tools
/
wb
/
fastexec
/
fastexec.s
< prev
next >
Wrap
Text File
|
1997-06-23
|
67KB
|
4,029 lines
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;$VER: FastExec.s 2.8 (10.6.97)
;by Torbjörn A. Andersson.
;Public Domain.
;
;Assemble with PhxAss (version 4.34), use OPT 3
;------------------------------------------------------------------------------;
;Max number of memory blocks for ADDMEM option
MAXADDMEM=10
;------------------------------------------------------------------------------;
_ArpBase = 0
_DOSBase = _ArpBase+4
_ExpansionBase = _DOSBase+4
_UtilityBase = _ExpansionBase+4
Args = _UtilityBase+4
ReturnCode = Args+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
bsr InitArp
tst.l d0
beq QuitError
move.l a2,a0
move.l d2,d0
lea Template(pc),a1
move.l a1,d1 ; template
lea ArgArray(pc),a1
move.l a1,d2 ; array
moveq #0,d3 ; args
bsr OSReadArgs
move.l d0,Args(a5)
beq QuitError
move.l ArgCACHE(pc),d0
beq .ArgCACHEOk
move.l d0,a0
bsr XToI
lea CacheBits(pc),a0
move.l d0,(a0)
.ArgCACHEOk
move.l ArgADDRESS(pc),d0
beq .ArgADDRESSOk
move.l d0,a0
bsr XToI
lea Address(pc),a0
move.l d0,(a0)
.ArgADDRESSOk
move.l ArgSYSINFO(pc),d0
beq .ArgSYSINFOOk
bsr SysInfo
bra Quit
.ArgSYSINFOOk
movem.l d2-d7/a2-a4,-(sp)
lea AddMemData(pc),a4
move.l ArgADDMEM(pc),a3
moveq #MAXADDMEM-1,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
movem.l d4-d7,(a4)
lea 16(a4),a4
dbf d3,.AddMemLoop2
;haven't specified more than we can handle, right?
tst.l (a3)
beq .AddMem2
.AddMemErr2
movem.l (sp)+,d2-d7/a2-a4
lea TxtAddMem(pc),a0 ; string
bra QuitPutS
.AddMem2
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
tst d0
bpl 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 Args(a5),d1 ; args
bsr OSFreeArgs
moveq #(_UtilityBase-_ArpBase)/4,d2
lea _ArpBase(a5),a2
.CloseLibrary
move.l (a2)+,a1 ; library
bsr OSCloseLibrary
dbf d2,.CloseLibrary
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 a6,a1 ; library
lea AddMemList(pc),a0
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
;------------------------------------------------------------------------------;
AddLibrary:
;first, add library with original function
bsr .AddLibrary
;try to move expansion.library
bsr MoveExpansion
addq.l #1,d0
beq .Rts ; not available, quit
;expansion.library has been moved (possibly failed to move, but don't retry)
;restore old function
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
;------------------------------------------------------------------------------;
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 d0-d3/a0/a1,-(sp)
move.l a0,d2 ; start of memory to add
move.l a0,d3
add.l d0,d3 ; end of memory to add
lea $0142(a6),a0 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a0),a0
tst.l (a0)
beq .Add
move.l a0,d0
moveq #$0020,d1 ; sizeof(MemHeader)
add.l a0,d1
bsr .Check
tst.l d0
bne .Err
movem.l $0014(a0),d0/d1 ; mh_Lower/mh_Upper
bsr .Check
tst.l d0
beq .Loop
.Err
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,d0-d3/a0/a1
.Rts
rts
.Check
; d0=start
; d1=end
; d2=start
; d3=end
; out d0=collision
cmp.l d0,d2
bcs .CheckCS
cmp.l d1,d2
bcs .CheckErr
.CheckOk
moveq #0,d0
rts
.CheckCS
cmp.l d0,d3
bls .CheckOk
.CheckErr
moveq #1,d0
rts
.Old
move.l OldAddMemList(pc),-(sp)
rts
.Add
movem.l (sp)+,d0-d3/a0/a1
;see if this is the memory we want exec.library to be in
;if it isn't, we'll just add it and quit
;if it is, we'll add it and move things to it
;assume it has the highest priority at the moment,
;so we get it when we just ask for fast memory
move.l d0,-(sp)
move.l ArgADDRESS(pc),d0
beq .AddressOk
cmp.l Address(pc),a0
beq .AddressOk
move.l (sp)+,d0
bsr .Old
jmp -$008A(a6) ; _LVOPermit
.AddressOk
move.l (sp)+,d0
;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 ArgFASTEXP(pc),d0
beq .Exp
bsr MoveExpansion
addq.l #1,d0
bne .Exp
;expansion.library hasn't been added yet
;patch AddLibrary() to do the job
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)
.Exp
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 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
;
;.Quit
jmp -$008A(a6) ; _LVOPermit
;------------------------------------------------------------------------------;
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 a2/a3,-(sp)
lea $0142(a6),a2 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),a2
tst.l (a2)
beq .Quit
move.l a2,a1 ; address
bsr MyTypeOfMem
tst d0
bmi .Loop
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
move.l a3,a2
cmp #36,$0014(a6) ; lib_Version
bcs .Loop
move.l a2,a1 ; memoryBlock
moveq #$0020,d0 ; byteSize, sizeof(MemHeader)
bsr FreeMemSafely
bra .Loop
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,a2/a3
rts
;------------------------------------------------------------------------------;
MoveExec:
movem.l d2-d7/a2-a5,-(sp)
move.l a6,a2
move.l a6,a1 ; address
bsr MyTypeOfMem
tst d0
bmi .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
bsr .Exp
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
move.b FlagEBExec(pc),d1
bne .End
and #-8,d0
.Free
bsr FreeMemSafely
.End
movem.l (sp)+,d2-d7/a2-a5
rts
;Update eb_ExecBase
.Exp
;expansion.library V36+ doesn't cache _SysBase
cmp #36,$0014(a6) ; lib_Version
bcc .ExpOk
lea expansion_library(pc),a1; libName
jsr -$0198(a6) ; _LVOOldOpenLibrary
tst.l d0
beq .ExpStack
move.l d0,a1 ; library
move.l a6,$0024(a1) ; eb_ExecBase
jmp -$019E(a6) ; _LVOCloseLibrary
.ExpStack
;expansion.library has not been added to library list
;get it from the stack, offset should be:
; 4 expansion jumps to addmemlist
; 4 addmemlist saves attributes
; 4 addmemlist saves cachebits
; 4 addmemlist jumps to MoveExec()
;40 MoveExec saves d2-d7/a2-a5
; 4 MoveExec jumps to .Exp()
;--
;60
moveq #$0024,d0 ; eb_ExecBase
add.l 60(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 (a1),a2
bne .ExpErr
move.l a6,(a1)
.ExpOk
rts
.ExpErr
lea FlagEBExec(pc),a0
st (a0)
rts
;------------------------------------------------------------------------------;
MoveExpansion:
; out d0=-1:expansion.library not found
; 0:couldn't move library
; 1:everything fine
;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 .ErrLib
move.l d0,a2
move.l a2,a1 ; address
bsr MyTypeOfMem
tst d0
bmi .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
.ErrLib
moveq #-1,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
;just in case MoveExec() couldn't update eb_ExecBase
cmp #36,$0014(a6) ; lib_Version
bcc .Rts
move.l a6,$0024(a3) ; eb_ExecBase
.Rts
rts
;------------------------------------------------------------------------------;
MoveIntrMem:
movem.l 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
tst d0
bmi .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
jsr -$0078(a6) ; _LVODisable
.Loop
move (a3)+,d0
beq .Quit
mulu #12,d0
move.l $54(a6,d0.l),a0
move.l a2,a1
move.l a2,$54(a6,d0.l)
lea $000E(a2),a2
move $000E(a0),(a2)+
cmp #36,$0014(a6) ; lib_Version
bcc .Copy
move $0010(a0),(a2)+
move.l $0012(a0),(a2)+
.Copy
bsr CopyList
bra .Loop
.Quit
jsr -$007E(a6) ; _LVOEnable
move.l a4,a1 ; memoryBlock
move.l d4,d0 ; byteSize
bsr FreeMemSafely
.End
movem.l (sp)+,d4/a2-a4
rts
.Table
dc.w 3,5,4,13,15,0
;------------------------------------------------------------------------------;
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
tst d0
bmi .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
move.l a1,-(sp)
bsr MyTypeOfMem
move.l (sp)+,a1
tst d0
bmi .Err
move.l a2,a0
move #255,d0
.Loop
move.l (a1)+,(a0)+
dbf d0,.Loop
move.l a2,d0
bsr SetVBR
jsr -$008A(a6) ; _LVOPermit
.End
move.l (sp)+,a2
rts
.Err
jsr -$008A(a6) ; _LVOPermit
moveq #1,d0 ; byteSize
ror #6,d0 ; 1024
move.l a2,a1 ; memoryBlock
jsr -$00D2(a6) ; _LVOFreeMem
bra .End
;------------------------------------------------------------------------------;
;modify all
; lea $4AFC4AFC,a6
;to load SysBase instead of zero.
;
;use $4AFC4AFC and not 0 so assembler won't change to sub.l a6,a6
PatchA6:
; a0=buff
; d0=size
move.l a0,a1
add.l d0,a1
.Loop
cmp.l a1,a0
bcc .Rts
cmp #$4DF9,(a0)+ ; lea x,a6
bne .Loop
cmp.l #$4AFC4AFC,(a0)
bne .Loop
move.l a6,(a0)+
bra .Loop
.Rts
rts
;------------------------------------------------------------------------------;
PatchInterrupts:
move.l a2,-(sp)
move.l #.EndLabel-.Int1,d0 ; byteSize
moveq #5,d1 ; requirements, MEMF_PUBLIC|MEMF_FAST
jsr -$00C6(a6) ; _LVOAllocMem
tst.l d0
beq .End
move.l d0,a2
lea .Int1(pc),a0 ; source
move.l d0,a1 ; dest
move.l #.EndLabel-.Int1,d0 ; size
jsr -$0276(a6) ; _LVOCopyMemQuick
bsr .Fix
move.l a2,a0 ; buffer
move.l #.EndLabel-.Int1,d0 ; size
bsr PatchA6
bsr OSCacheClearU
jsr -$0084(a6) ; _LVOForbid
bsr GetVBR
move.l d0,a1
move.l a2,$64(a1)
lea .Int2-.Int1(a2),a0
move.l a0,$68(a1)
lea .Int3-.Int1(a2),a0
move.l a0,$6C(a1)
lea .Int4-.Int1(a2),a0
move.l a0,$70(a1)
lea .Int5-.Int1(a2),a0
move.l a0,$74(a1)
lea .Int6-.Int1(a2),a0
move.l a0,$78(a1)
bsr OSCacheClearU
jsr -$008A(a6) ; _LVOPermit
; moveq #1,d0
.End
move.l (sp)+,a2
rts
.Fix
cmp #36,$0014(a6) ; lib_Version
bcc .FixRts
;kickstart V33/V34 doesn't save a6 on stack for ExitIntr()
;overwrite it with the two instructions that follows
;put a nop-instruction in the space left over
move.l a2,a0
lea .Int4-.Int1(a2),a1
.FixLoop
cmp.l a1,a0
bcc .FixNext
cmp #$2F0E,(a0)+ ; move.l a6,-(sp)
bne .FixLoop
move.l (a0),-2(a0)
move 4(a0),2(a0)
move #$4E71,4(a0) ; nop
bra .FixLoop
.FixNext
lea .Next4-.Int1(a2),a0
cmp.l a1,a0
lea .EndLabel-.Int1(a2),a1
bcc .FixLoop
.FixRts
rts
;basic changes from kickstart 39.106:
;
;1. SysBase is coded in lea-instructions
; - much faster than reading from location $4
;2. changed order in "and $001E(a0),d1/move.l (4).w,a6"
; - second read from chip seems faster when done later
;3. changed one "btst #7,d1/beq" to "tst.b d1/bpl"
; - shorter, faster
;4. changed "add #12,sp" to "lea 12(sp),sp"
; - faster
cnop 0,4
.Int1:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move $001C(a0),d1
btst #14,d1
beq .Done1
lea $4AFC4AFC,a6
and $001E(a0),d1
btst #0,d1
beq .Next1a
movem.l $0054(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next1a
btst #1,d1
beq .Next1b
movem.l $0060(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next1b
btst #2,d1
beq .Quit1
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
.Quit1
movem.l (sp)+,d0/d1/a0/a1/a5/a6
rte
cnop 0,4
.Int2:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move $001C(a0),d1
btst #14,d1
beq .Done1
lea $4AFC4AFC,a6
and $001E(a0),d1
btst #3,d1
beq .Quit1
movem.l $0078(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
.Int3:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move $001C(a0),d1
btst #14,d1
beq .Done3
lea $4AFC4AFC,a6
and $001E(a0),d1
btst #6,d1
beq .Next3a
movem.l $009C(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next3a
btst #5,d1
beq .Next3b
movem.l $0090(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next3b
btst #4,d1
beq .Quit3
movem.l $0084(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Quit3
movem.l (sp)+,d0/d1/a0/a1/a5/a6
rte
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 $001C(a0),d1
btst #14,d1
beq .Done3
lea $4AFC4AFC,a6
and $001E(a0),d1
.Loop4
btst #8,d1
beq .Next4a
movem.l $00B4(a6),a1/a5
move.l a6,-(sp)
pea .Next4(pc)
jmp (a5)
cnop 0,4
.Next4a
btst #10,d1
beq .Next4b
movem.l $00CC(a6),a1/a5
move.l a6,-(sp)
pea .Next4(pc)
jmp (a5)
cnop 0,4
.Next4b
tst.b d1
bpl .Next4c
movem.l $00A8(a6),a1/a5
move.l a6,-(sp)
pea .Next4(pc)
jmp (a5)
cnop 0,4
.Next4c
btst #9,d1
beq .Quit3
movem.l $00C0(a6),a1/a5
move.l a6,-(sp)
pea .Next4(pc)
jmp (a5)
cnop 0,4
.Next4
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
nop
cnop 0,4
.Int5:
movem.l d0/d1/a0/a1/a5/a6,-(sp)
lea $DFF000,a0
move $001C(a0),d1
btst #14,d1
beq .Done5
lea $4AFC4AFC,a6
and $001E(a0),d1
btst #12,d1
beq .Next5a
movem.l $00E4(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next5a
btst #11,d1
beq .Quit5
movem.l $00D8(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Quit5
movem.l (sp)+,d0/d1/a0/a1/a5/a6
rte
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 $001C(a0),d1
btst #14,d1
beq .Done5
lea $4AFC4AFC,a6
and $001E(a0),d1
btst #14,d1
beq .Next6a
movem.l $00FC(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.Next6a
btst #13,d1
beq .Quit5
movem.l $00F0(a6),a1/a5
move.l a6,-(sp)
pea -$0024(a6) ; _LVOExitIntr
jmp (a5)
cnop 0,4
.EndLabel
;------------------------------------------------------------------------------;
;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
;------------------------------------------------------------------------------;
CmpMem:
; a0=address1
; a1=address2
; out d0=1 if addresses are within same mh_Lower/mh_Upper
movem.l a2/a3,-(sp)
moveq #0,d0
lea $0142(a6),a2 ; MemList
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),a2
tst.l (a2)
beq .Quit
lea $0020(a2),a3 ; sizeof(MemHeader)
cmp.l $0014(a2),a3 ; mh_Lower
beq .LowerOk
move.l $0014(a2),a3 ; mh_Lower
.LowerOk
cmp.l a3,a1
bcs .Loop
cmp.l $0018(a2),a1 ; mh_Upper
bcc .Loop
cmp.l a3,a0
bcs .Quit
cmp.l $0018(a2),a0 ; mh_Upper
bcc .Quit
moveq #1,d0
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,a2/a3
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
;Called by functions like MoveSSP
;Only free if FREEOLD option is used.
FreeMemSafely:
move.l ArgFREEOLD(pc),d1
beq .Rts
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 .Quit ; lower than=>chip
moveq #1,d0 ; MEMF_SLOW
cmp.l #$00C00000,a1 ; start of ranger memory
bcs .Type
cmp.l #$00DC0000,a1 ; end of ranger memory
bcs .Quit
.Type
move.l a1,-(sp)
jsr -$0216(a6) ; _LVOTypeOfMem
move.l (sp)+,a1
moveq #6,d1 ; MEMF_CHIP|MEMF_FAST
and.l d1,d0 ; wipe out our slow flag
bne .Quit
moveq #4,d0 ; MEMF_FAST
.Quit
move.l ArgADDRESS(pc),d1
bne .Cmp
btst #2,d0 ; MEMB_FAST
bne .Ok
rts
.Ok
or #$8000,d0
rts
.Cmp
move.l Address(pc),a0
move.l d0,-(sp)
bsr CmpMem
move.l d0,d1
move.l (sp)+,d0
tst.l d1
bne .Ok
rts
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
expansion_library dc.b 'expansion.library',0
FastExecName dc.b 'FastExec',0
dc.b '$VER: '
FastExecId dc.b 'FastExec 2.8 (10.6.97)',13,10,0
cnop 0,4
ArgArray
ArgSYSINFO dc.l 0
ArgREBOOT dc.l 0
ArgNOEXEC dc.l 0
ArgADDRESS dc.l 0
ArgFREEOLD 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
Address dc.l 0
CacheBits dc.l 0
OldAddMemList dc.l 0
AddMemData dcb.l MAXADDMEM*4,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_ERmanufact = ibrd_boardsize+4
ibrd_flags = ibrd_ERmanufact+2
ibrd_ERtype = ibrd_flags+1
ibrd_ERproduct = ibrd_ERtype+1
ibrd_ERflags = ibrd_ERproduct+1
ibrd_sizeof = ibrd_ERflags+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
ikickmem_next = 0
ikickmem_name = ikickmem_next+4
ikickmem_addr = ikickmem_name+4
ikickmem_start = ikickmem_addr+4
ikickmem_size = ikickmem_start+4
ikickmem_num = ikickmem_size+4
ikickmem_sizeof = ikickmem_num+2
;------------------------------------------------------------------------------;
SysInfo:
movem.l d2-d7/a2-a5,-(sp)
move.l sp,d7
lea -1024(sp),sp
move.l sp,a3
lea -20*4(sp),sp
move.l sp,a4
move.l a4,a2
;Exec
move.l $0014(a6),(a2)+ ; lib_Version/lib_Revision
;Kickstart
bsr GetKSVer
move.l d0,(a2)+
;Workbench
bsr GetWBVer
move.l d0,(a2)+
;SetPatch
bsr GetSPVer
move.l d0,(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)+
lea $002A(a6),a0 ; ColdCapture
moveq #5,d0
.Init
move.l (a0)+,(a2)+
dbf d0,.Init
; move.l $002A(a6),(a2)+ ; ColdCapture
; move.l $002E(a6),(a2)+ ; CoolCapture
; move.l $0032(a6),(a2)+ ; WarmCapture
; move.l $0036(a6),(a2)+ ; SysStkUpper
; move.l $003A(a6),(a2)+ ; SysStkLower
; move.l $003E(a6),(a2)+ ; MaxLocMem
move.l $004E(a6),(a2)+ ; MaxExtMem
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 SysIKickMem
tst.l d0
beq .Rts
bsr PutLF
bsr SysIKickTag
tst.l d0
beq .Rts
bsr PutLF
bsr SysIRes
.Rts
rts
.FmtMisc
dc.b 'Exec: %d.%d',10
dc.b 'Kickstart: %d.%d',10
dc.b 'Workbench: %d.%d',10
dc.b 'SetPatch: %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 'SysStkUpper: $%08lx',10
dc.b 'SysStkLower: $%08lx',10
dc.b 'MaxLocMem: $%08lx',10
dc.b 'MaxExtMem: $%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 ibrd_ERmanufact(a4),d0
move.l d0,-(sp)
moveq #0,d0
move.b ibrd_ERflags(a4),d0
move.l d0,-(sp)
moveq #0,d0
move.b ibrd_ERproduct(a4),d0
move.l d0,-(sp)
moveq #0,d0
move.b ibrd_ERtype(a4),d0
move.l d0,-(sp)
move.l ibrd_boardsize(a4),-(sp)
move.l ibrd_boardaddr(a4),-(sp)
moveq #0,d0
move.b ibrd_flags(a4),d0
move.l d0,-(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 Flags BoardAddr BoardSize Type Product Flags Manufacturer',10,0
.Fmt
dc.b '$%08lx $%02lx $%08lx $%08lx $%02lx %7ld $%02lx %12ld',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
;------------------------------------------------------------------------------;
SysIKickMem:
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 GetIKickMem
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.l ikickmem_size(a4),-(sp)
move.l ikickmem_start(a4),-(sp)
lea .Fmt2(pc),a0 ; formatString
tst.l ikickmem_addr(a4)
beq .FmtOk
moveq #0,d0
move ikickmem_num(a4),d0
move.l d0,-(sp)
move.l ikickmem_name(a4),-(sp)
move.l ikickmem_addr(a4),-(sp)
lea .Fmt1(pc),a0 ; formatString
tst.l d0
bne .FmtOk
lea .Fmt0(pc),a0 ; formatString
.FmtOk
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 'KICKMEM:',10
dc.b 'Address Name NumEntries Address Length',10,0
.Fmt0
dc.b '$%08lx %-20.20s %5ld',10,0
.Fmt1
dc.b '$%08lx %-20.20s %5ld $%08lx $%08lx',10,0
.Fmt2
dc.b ' $%08lx $%08lx',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIKickTag:
lea .Str(pc),a0 ; string
move.l $0226(a6),a1 ; ptr, KickTagPtr
bra SysIModules
.Str
dc.b 'KICKTAG:',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIRes:
lea .Str(pc),a0 ; string
move.l $012C(a6),a1 ; ptr, ResModules
bra SysIModules
.Str
dc.b 'RESIDENTS:',10,0
cnop 0,2
;------------------------------------------------------------------------------;
SysIModules:
; a0=string
; a1=ptr
movem.l d2-d4/a2-a4,-(sp)
lea -80(sp),sp
move.l sp,a3
lea -20(sp),sp
move.l sp,d4
move.l a1,a2
; move.l #0,a0 ; string
moveq #1,d0
bsr PutS
tst.l d0
beq .End
lea .Str(pc),a0 ; string
moveq #1,d0
bsr PutS
tst.l d0
beq .End
move.l a2,d0
beq .Ok
.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)
moveq #0,d0
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 d4,a1
move.l $000E(a4),d0 ; rt_Name
beq .Ok2
move.l d0,a0
.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 '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.b $000E(a2),ibrd_flags(a3); cd_Flags
move.b $0010(a2),ibrd_ERtype(a3); cd_Rom+er_Type
move.b $0011(a2),ibrd_ERproduct(a3); cd_Rom+er_Product
move.b $0012(a2),ibrd_ERflags(a3); cd_Rom+er_Flags
move $0014(a2),ibrd_ERmanufact(a3); cd_Rom+er_Manufacturer
move.l $0020(a2),ibrd_boardaddr(a3); cd_BoardAddr
move.l $0024(a2),ibrd_boardsize(a3); cd_BoardSize
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
;------------------------------------------------------------------------------;
GetIKickMem:
movem.l d2/d3/a2-a4,-(sp)
moveq #0,d2
lea $0222(a6),a2 ; KickMemPtr
jsr -$0084(a6) ; _LVOForbid
.Loop
move.l (a2),d0
beq .Ok
move.l d0,a2
bsr .Alloc
beq .Err
move.l a2,a0
bsr GetIName
moveq #-1,d1
cmp.l d1,d0
beq .Err
move.l d0,ikickmem_name(a3)
move.l a2,ikickmem_addr(a3)
move $000E(a2),d3
move d3,ikickmem_num(a3)
beq .Loop
lea $0010(a2),a4
move.l (a4)+,ikickmem_start(a3)
move.l (a4)+,ikickmem_size(a3)
.Loop2
subq #1,d3
beq .Loop
bsr .Alloc
beq .Err
move.l (a4)+,ikickmem_start(a3)
move.l (a4)+,ikickmem_size(a3)
bra .Loop2
.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/d3/a2-a4
rts
.Alloc
moveq #ikickmem_sizeof,d0 ; byteSize
moveq #1,d1 ; requirements
swap d1 ; MEMF_CLEAR
bsr OSAllocVec
tst.l d0
bne .Insert
rts
.Insert
tst.l d2
beq .InsertFirst
move.l d0,(a3)
.InsertOk
move.l d0,a3
clr.l (a3)
moveq #1,d0
rts
.InsertFirst
move.l d0,d2
bra .InsertOk
;------------------------------------------------------------------------------;
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,a0
bsr .Strip
move.l a2,d0
.End
move.l (sp)+,a2
rts
.Err
moveq #-1,d0
bra .End
.Strip
move.b (a0)+,d0
beq .StripRts
cmp.b #10,d0
beq .StripOk
cmp.b #13,d0
bne .Strip
.StripOk
clr.b -(a0)
.StripRts
rts
;------------------------------------------------------------------------------;
GetMemStr:
; d0=attributes
lea .fast(pc),a0
btst #2,d0 ; MEMB_FAST
bne .Ok
lea .chip(pc),a0
btst #1,d0 ; MEMB_CHIP
bne .Ok
lea .slow(pc),a0
btst #0,d0
bne .Ok
lea .chip(pc),a0
.Ok
move.l a0,d0
rts
.chip dc.b 'chip',0
.fast dc.b 'fast',0
.slow dc.b 'slow',0
cnop 0,2
;------------------------------------------------------------------------------;
GetKSVer:
move $0014(a6),d0 ; lib_Version
move.l d0,d1
swap d0
move $0022(a6),d0 ; SoftVer
cmp #36,d1
bcc .Rts
;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 .Rts
move (a0),d0
.Rts
rts
;------------------------------------------------------------------------------;
;SetPatchSemaphore:
;sps_Sem = $0000
;sps_Private = $002E
;sps_Version = $003A
;sps_Revision = $003C
GetSPVer:
lea .s(pc),a1 ; name
jsr -$0084(a6) ; _LVOForbid
jsr -$0252(a6) ; _LVOFindSemaphore
jsr -$008A(a6) ; _LVOPermit
tst.l d0
beq .Rts
move.l d0,a0
move.l $003A(a0),d0 ; sps_Version/sps_Revision
.Rts
rts
.s
dc.b '« SetPatch »',0
cnop 0,2
;------------------------------------------------------------------------------;
GetWBVer:
move.l d2,-(sp)
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 .Done
move.l d0,a1 ; library
move.l $0014(a1),d2 ; lib_Version/lib_Revision
jsr -$019E(a6) ; _LVOCloseLibrary
.Done
move.l d2,d0
move.l (sp)+,d2
rts
;------------------------------------------------------------------------------;
GetTypeString:
; d0=type
moveq #19,d1 ; NT_DEATHMESSAGE
cmp.l d1,d0
bhi .Err
lea .s(pc),a0
bra .Next
.Loop
tst.b (a0)+
bne .Loop
.Next
dbf d0,.Loop
move.l a0,d0
rts
.Err
moveq #0,d0
rts
.s
dc.b 'unknown',0
dc.b 'task',0
dc.b 'interrupt',0
dc.b 'device',0
dc.b 'msgport',0
dc.b 'message',0
dc.b 'freemsg',0
dc.b 'replymsg',0
dc.b 'resource',0
dc.b 'library',0
dc.b 'memory',0
dc.b 'softint',0
dc.b 'font',0
dc.b 'process',0
dc.b 'semaphore',0
dc.b 'signalsem',0
dc.b 'bootnode',0
dc.b 'kickmem',0
dc.b 'graphics',0
dc.b 'deathmessage',0
cnop 0,2
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
Usage:
lea TxtUsage(pc),a0 ; string
moveq #0,d0
bsr PutS
bra Quit
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;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
;------------------------------------------------------------------------------;
FindKickTag:
; a0=name
movem.l a2/a3,-(sp)
move.l a0,a3
jsr -$0084(a6) ; _LVOForbid
move.l $0226(a6),d0 ; KickTagPtr
beq .Quit
move.l d0,a2
.Loop
move.l (a2)+,d0
beq .Quit
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
.Quit
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,a2/a3
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
;------------------------------------------------------------------------------;
InitArp:
cmp #36,$0014(a6) ; lib_Version
bcc .Ok
lea .Name(pc),a1 ; libName
moveq #33,d0 ; version
jsr -$0228(a6) ; _LVOOpenLibrary
move.l d0,_ArpBase(a5)
bne .Ok
lea .Txt(pc),a0
move.l a0,d1 ; str
bsr OSPutStr
moveq #0,d0
rts
.Ok
moveq #1,d0
rts
.Name
dc.b 'arp.library',0
.Txt
dc.b 'you need arp.library V33+',10,0
cnop 0,2
;------------------------------------------------------------------------------;
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
;resident tag already installed?
move.l a1,a0 ; name
bsr FindKickTag
tst.l d0
bne .Err
;allocate memory for resident tag
;need to allocate sizeof(MemChunk) bytes extra before the tag
;at boot time those bytes can be overwritten
moveq #$0042,d0 ; sizeof(MemChunk)+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
addq.l #8,a2 ; sizeof(MemChunk)
lea $0020(a2),a3 ; sizeof(MemList)+8
lea $001A(a3),a4 ; sizeof(Resident)
;copy resident module
move.l d2,a0 ; source
move.l a4,a1 ; dest
move.l d6,d0 ; size
jsr -$0276(a6) ; _LVOCopyMemQuick
bsr OSCacheClearU
;init resident tag
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,$000A(a2) ; ln_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
;init MemList for KickMemPtr
lea $000E(a2),a1 ; ml_NumEntries
move #1,(a1)+ ; NumEntries
move.l a2,d0
subq.l #8,d0
move.l d0,(a1)+ ; Address
moveq #$0042,d0 ; sizeof(MemChunk)+sizeof(MemList)+8+sizeof(Resident)
add.l d6,d0
move.l d0,(a1)+ ; Length
;init long-word arrary for KickTagPtr
move.l a3,(a1)+ ; Resident
; clr.l (a1)+
;set KickMemPtr and KickTagPtr
move.l a2,a0 ; ptr
bsr SetKickPtrs
moveq #1,d0
.End
movem.l (sp)+,d2-d7/a2-a4
rts
.Err
moveq #-1,d0
bra .End
;------------------------------------------------------------------------------;
OSAllocMem:
cmp #39,$0014(a6) ; lib_Version
bcs .Old
.OS
jmp -$00C6(a6) ; _LVOAllocMem
.Old
bclr #10,d1 ; MEMB_KICK
beq .KickOk
or #$0100,d1 ; MEMF_LOCAL
.KickOk
cmp #36,$0014(a6) ; lib_Version
bcc .OS
bclr #8,d1 ; MEMB_LOCAL
beq .LocalOk
or #$0002,d1 ; MEMF_CHIP
.LocalOk
btst #18,d1 ; MEMB_REVERSE
bne .Reverse
bsr .OS
.Done
tst.l d0
beq .Error
.Rts
rts
.Error
move.l $0114(a6),a0 ; ThisTask
cmp.b #13,$0008(a0) ; ln_Type, NT_PROCESS
bne .Rts
moveq #103,d1 ; ERROR_NO_FREE_STORE
move.l d1,$0094(a0) ; pr_Result2
rts
.Reverse
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
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
.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
bra .Done
.Err
jsr -$008A(a6) ; _LVOPermit
moveq #0,d0
bra .End
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
OSCloseLibrary:
move.l a1,d0
beq .Rts
jmp -$019E(a6) ; _LVOCloseLibrary
.Rts
rts
;------------------------------------------------------------------------------;
OSColdReboot:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
jsr -$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)
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
move.l d2,a0 ; string
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
;------------------------------------------------------------------------------;
OSReadArgs:
cmp #36,$0014(a6) ; lib_Version
bcs .Old
movem.l d2/a6,-(sp)
move.l _DOSBase(a5),a6
jsr -$031E(a6) ; _LVOReadArgs
tst.l d0
bne .End
jsr -$0084(a6) ; _LVOIoErr
move.l d0,d1 ; code
moveq #0,d2 ; header
jsr -$01DA(a6) ; _LVOPrintFault
moveq #0,d0
.End
movem.l (sp)+,d2/a6
rts
.Old
movem.l d3/a2/a3/a6,-(sp)
move.l d1,a3
movem.l d0/a0,-(sp)
move.l d1,a0 ; s
bsr StrLen
addq.l #6,d0 ; '...'-'M'+NULL+pad(=3)
and #-4,d0
move.l d0,d3
movem.l (sp)+,d0/a0
sub.l d3,sp
move.l sp,a1
;Arp uses /... instead of /M
.MLoop
move.b (a3)+,d1
move.b d1,(a1)+
beq .MDone
cmp.b #'/',d1
bne .MLoop
cmp.b #'M',(a3)
bne .MLoop
addq.l #1,a3
move.b #'.',(a1)+
move.b #'.',(a1)+
move.b #'.',(a1)+
bra .MLoop
.MDone
; move.l #0,a0 ; line
; move.l #0,d0 ; len
sub.l a1,a1 ; help
move.l d2,a2 ; args
move.l sp,a3 ; tplate
move.l _ArpBase(a5),a6
jsr -$00FC(a6) ; _LVOGADS
tst.l d0
blt .Err
moveq #1,d0
.Done
add.l d3,sp
movem.l (sp)+,d3/a2/a3/a6
rts
.Err
move.l (a2),a1 ; string
jsr -$00F0(a6) ; _LVOPuts
moveq #0,d0
bra .Done
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
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
;------------------------------------------------------------------------------;
SetKickPtrs:
; a0=ptr
;a0 points to MemEntry to be set in KickMemPtr
;right after comes long-word array to be set in KickTagPtr
movem.l a2-a4,-(sp)
;MemEntry -> a2
move.l a0,a2
;end of MemEntry -> a3
moveq #0,d0
move $000E(a0),d0 ; ml_NumEntries
beq .NumOk
subq.l #1,d0
lsl.l #3,d0
.NumOk
lea $0018(a2),a3 ; sizeof(MemList)
add.l d0,a3
;end of long-word array -> a4
move.l a3,a4
.ArrayLoop
move.l (a4),d0
beq .ArrayEnd
addq.l #4,a4
bclr #31,d0
beq .ArrayLoop
move.l d0,a4
bra .ArrayLoop
.ArrayEnd
jsr -$0084(a6) ; _LVOForbid
;link with KickMemPtr
move.l $0222(a6),(a2) ; KickMemPtr
move.l a2,$0222(a6) ; KickMemPtr
;link with KickTagPtr
move.l $0226(a6),d0 ; KickTagPtr
beq .Tag
bset #31,d0
move.l d0,(a4)
.Tag
move.l a3,$0226(a6) ; KickTagPtr
;set KickCheckSum
jsr -$0264(a6) ; _LVOSumKickData
move.l d0,$022A(a6) ; KickCheckSum
;push data cache
bsr OSCacheClearU
jsr -$008A(a6) ; _LVOPermit
movem.l (sp)+,a2-a4
rts
;------------------------------------------------------------------------------;
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 'Out of memory',10,0
TxtExpansion dc.b 'Can''t find expansion.library in ResModules list',10,0
TxtExec dc.b 'exec.library is already in fast memory - you don''t need this program',10,0
TxtAddMem dc.b 'Bad arguments for ADDMEM option',10,0
Str68881 dc.b '68881',0
Str68882 dc.b '68882',0
StrFPU40 dc.b '68040 FPU',0
StrNONE dc.b 'none',0
;------------------------------------------------------------------------------;
Template
dc.b 'SYSINFO/S,REBOOT/S,NOEXEC/S,ADDRESS/K,FREEOLD/S,PATCH/S,FASTSSP/S,FASTVBR/S,FASTEXP/S,FASTMEM/S,FASTINT/S,CACHE/K,ADDMEM/K/M',0
;------------------------------------------------------------------------------;
TxtUsage
dc.b 'FastExec 2.8 (10.6.97)',10
dc.b 'Torbjörn A. Andersson.',10
dc.b 'Public Domain.',10
dc.b 10
dc.b 'Usage: FastExec [SYSINFO] [REBOOT] [NOEXEC] [FREEOLD] [PATCH]',10
dc.b ' [FASTSSP] [FASTVBR] [FASTEXP] [FASTMEM] [FASTINT]',10
dc.b ' [CACHE 0xhhhhhhhh] [ADDRESS 0xhhhhhhhh]',10
dc.b ' [ADDMEM <base size attr pri> ...]',10
dc.b 0
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
END
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;
;------------------------------------------------------------------------------;