home *** CD-ROM | disk | FTP | other *** search
- **
- ** VMEM - a virtual memory manager for the Amiga operating system
- **
- ** Version 0.1 ⌐1990 by Edward Hutchins
- ** Based in part on the SetCPU program by Dave Haynie
- ** Authors:
- **
- ** Edward Hutchins: eah1@cec1.wustl.edu
- ** Loren Rittle: l-rittle@uiuc.edu
- **
- ** Revisions:
- ** 12/19/91 code released as freeware under the GNU general public license - Ed.
- **
- ** This program is free software; you can redistribute it and/or modify
- ** it under the terms of the GNU General Public License as published by
- ** the Free Software Foundation; either version 1, or (at your option)
- ** any later version.
- **
- ** This program is distributed in the hope that it will be useful,
- ** but WITHOUT ANY WARRANTY; without even the implied warranty of
- ** MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
- ** GNU General Public License for more details.
- **
- ** You should have received a copy of the GNU General Public License
- ** along with this program; if not, write to the Free Software
- ** Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
- **
-
- CSECT code
-
- **
- ** Global variables from VMEM.C
- **
-
- XREF _PhysicalPages ; UWORD
- XREF _VirtualPages ; UWORD
- XREF _ROMBase ; APTR
- XREF _PhysBase ; APTR
- XREF _PageTable ; PD_SHORT * (ULONG)
- XREF _PhysPageDesc ; PHYS_DESC * (UBYTE)
- XREF _SysBusErrHandler ; *()
- XREF _PageDaemonTask ; struct Task *
- XREF _PageDaemonSig ; ULONG
- XREF _FastMemHeader ; struct MemHeader *
- XREF _PageFaultList ; struct MinList
- XREF _PendingPageFaults ; UWORD
-
- **
- ** Exported functions in this module
- **
-
- XDEF _GetCPUType ; ID the CPU
- XDEF _GetCACR ; Get 020/030 CACR register
- XDEF _SetCACR ; Set 020/030 CACR register
- XDEF _GetMMUType ; Returns the type of MMU
- XDEF _GetCRP ; Gets MMU CRP register
- XDEF _SetCRP ; Sets MMU CRP register
- XDEF _GetTC ; Gets MMU TC register
- XDEF _SetTC ; Gets MMU TC register
- XDEF _GetFPUType ; Gets the FPU type
- XDEF _InsertFaultHandler ; sets up the fault handler
- XDEF _HandlePageFault ; make visible to the debugger
- XDEF _RestartTask ; make visible to the debugger
-
- **
- ** External functions
- **
-
- XREF _AbsExecBase
- XREF _LVOFindTask
- XREF _LVOAllocTrap
- XREF _LVOFreeTrap
- XREF _LVOAllocate
- XREF _LVODeallocate
- XREF _LVOAllocSignal
- XREF _LVOFreeSignal
- XREF _LVOSignal
- XREF _LVOWait
- XREF _LVOSupervisor
- XREF _LVOForbid
- XREF _LVOPermit
- XREF _LVODisable
- XREF _LVOEnable
-
- **
- ** Macros & constants used herein...
- **
-
- CALLSYS macro *
- jsr _LVO\1(A6)
- endm
-
- CIB_ENABLE equ 0
- CIB_FREEZE equ 1
- CIB_ENTRY equ 2
- CIB_CLEAR equ 3
- CIB_BURST equ 4
-
- CDB_ENABLE equ 8
- CDB_FREEZE equ 9
- CDB_ENTRY equ 10
- CDB_CLEAR equ 11
- CDB_BURST equ 12
- CDB_WALLOC equ 13
-
- AFB_68030 equ 2
-
- ATNFLGS equ $129
-
- ** mask off the vector information
- SS_VECTOR equ $6
- SS_FORMAT_MASK equ $F000
-
- ** short bus cycle fault stack frame (16 words)
- SSF_SIZE equ $20
- SSF_LSIZE equ $08 ; size in longwords
- SSF_FORMAT equ $A000
-
- SSF_SR equ $0
- SSF_PC equ $2
- SSF_VECTOR equ $6
- SSF_SSR equ $A
- SSF_PIPE_C equ $C
- SSF_PIPE_B equ $E
- SSF_DATA_ADDR equ $10
- SSF_DOB equ $18
-
- ** long bus cycle fault stack frame (46 words)
- LSF_SIZE equ $5C
- LSF_LSIZE equ $17 ; size in longwords
- LSF_FORMAT equ $B000
-
- LSF_SR equ $0
- LSF_PC equ $2
- LSF_VECTOR equ $6
- LSF_SSR equ $A
- LSF_PIPE_C equ $C
- LSF_PIPE_B equ $E
- LSF_DATA_ADDR equ $10
- LSF_DOB equ $18
- LSF_STAGEB_ADDR equ $24
- LSF_DIB equ $2C
-
- ** special status bits
- SSTAT_FC equ $8000 ; fault on stage C of the instruction pipe
- SSTAT_FB equ $4000 ; fault on stage B
- SSTAT_RC equ $2000 ; stage C re-run
- SSTAT_RB equ $1000 ; stage B re-run
- SSTAT_DF equ $0100 ; data fault
- SSTAT_RM equ $0080 ; read-modify-write cycle
- SSTAT_RW equ $0040 ; read/write indicator
- SSTAT_SIZE_MASK equ $0030 ; size of data transfer
-
- ** the size of a fault node - 1K
- FAULTNODE_SIZE equ $400
- FAULT_FRAME equ 80 ; Frame in FaultNode -> 8 + 15*4 + 4 + 4 + 4
-
- **
- ** Need just a little more stuff
- **
-
- NOLIST
- include "exec/execbase.i"
- include "exec/tasks.i"
- include "exec/lists.i"
- LIST
-
- ***********************************************************************
- **
- ** This section contains functions that identify and operate on CPU
- ** things.
- **
- ***********************************************************************
-
- ;======================================================================
- ;
- ; This function returns the type of the CPU in the system as a
- ; longword: 68000, 68010, 68020, or 68030. The testing must be done
- ; in reverse order, in that any higher CPU also has the bits set for
- ; a lower CPU. Also, since 1.3 doesn't recognize the 68030, if I
- ; find the 68020 bit set, I always check for the presence of a
- ; 68030.
- ;
- ; This routine should be the first test routine called under 1.2
- ; and 1.3.
- ;
- ; ULONG GetCPUType();
- ;
- ;======================================================================
-
- _GetCPUType:
- movem.l a4/a5,-(sp) ; Save this register
- move.l _AbsExecBase,a6 ; Get ExecBase
- btst.b #AFB_68030,ATNFLGS(a6) ; Does the OS think an '030 is here?
- beq.s 0$
- move.l #68030,d0 ; Sure does...
- movem.l (sp)+,a4/a5
- rts
-
- 0$ btst.b #AFB_68020,ATNFLGS(a6) ; Maybe a 68020
- bne.s 2$
- btst.b #AFB_68010,ATNFLGS(a6) ; Maybe a 68010?
- bne.s 1$
- move.l #68000,d0 ; Just a measley '000
- movem.l (sp)+,a4/a5
- rts
-
- 1$ move.l #68010,d0 ; Yup, we're an '010
- movem.l (sp)+,a4/a5
- rts
-
- 2$ move.l #68020,d0 ; Assume we're an '020
- lea 3$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- movem.l (sp)+,a4/a5
- rts
-
- 3$ movec cacr,d1 ; Get the cache register
- move.l d1,a4 ; Save it for a minute
- bset.l #CIB_BURST,d1 ; Set the inst burst bit
- bclr.l #CIB_ENABLE,d1 ; Clear the inst cache bit
- movec d1,cacr ; Try to set the CACR
- movec cacr,d1
- btst.l #CIB_BURST,d1 ; Do we have a set burst bit?
- beq.s 4$
- move.l #68030,d0 ; It's a 68030
- bset.b #AFB_68030,ATNFLGS(a6)
-
- 4$ move.l a4,d1 ; Restore the original CACR
- movec d1,cacr
- rte
-
- ;======================================================================
- ;
- ; This function returns the 68020/68030 CACR register. It assumes
- ; a 68020 or 68030 based system.
- ;
- ; ULONG GetCACR()
- ;
- ;======================================================================
-
- _GetCACR:
- move.l _AbsExecBase,a6 ; Get ExecBase
- btst.b #AFB_68020,ATNFLGS(a6) ; Does the OS think an '020 is here?
- bne.s 1$
- moveq #0,d0 ; No CACR here, pal
- rts
-
- 1$ move.l a5,-(sp) ; Save this register
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5 ; Give back registers
- rts
-
- 2$ movec cacr,d0 ; Make CACR the return value
- rte
-
- ;======================================================================
- ;
- ; This function sets the value of the 68020/68030 CACR register.
- ; It assumes a 68020 or 68030 based system.
- ;
- ; void SetCACR(cacr)
- ; ULONG cacr;
- ;
- ;======================================================================
-
- _SetCACR:
- move.l 4(sp),d0 ; New CACR is on stack
- move.l _AbsExecBase,a6 ; Get ExecBase
- btst.b #AFB_68020,ATNFLGS(a6) ; Does the OS think an '020 is here?
- bne.s 1$
- rts ; No CACR here, pal
-
- 1$ move.l a5,-(sp) ; Save this register
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5 ; Give back register
- rts
-
- 2$ movec d0,cacr ; Set the CACR
- rte
-
- ***********************************************************************
- **
- ** Functions that identify and operate on MMU things.
- **
- ***********************************************************************
-
- ;======================================================================
- ;
- ; This function returns 0L if the system contains no MMU,
- ; 68851L if the system does contain an 68851, or 68030L if the
- ; system contains a 68030.
- ;
- ; This routine seems to lock up on at least some CSA 68020
- ; boards, though it runs just fine on those from Ronin and
- ; Commodore, as well as all 68030 boards it's been tested on.
- ;
- ; ULONG GetMMUType()
- ;
- ;======================================================================
-
- _GetMMUType:
- move.l _AbsExecBase,a6 ; Get ExecBase
- movem.l a3/a4/a5,-(sp) ; Save this stuff
- moveq #0,d0
- move.l d0,a1
- CALLSYS FindTask ; Call FindTask(0L)
- move.l d0,a3
-
- move.l TC_TRAPCODE(a3),a4 ; Change the exception vector
- move.l #2$,TC_TRAPCODE(a3)
-
- subq.l #4,sp ; Let's try an MMU instruction
- pmove tc,(sp)
- cmpi #0,d0 ; Any MMU here?
- beq.s 1$
- btst.b #AFB_68030,ATNFLGS(a6) ; Does the OS think an '030 is here?
- beq.s 1$
- move.l #68030,d0
-
- 1$ addq.l #4,sp ; Return that local
- move.l a4,TC_TRAPCODE(a3) ; Reset exception stuff
- movem.l (sp)+,a3/a4/a5 ; and return the registers
- rts
-
- ; This is the exception code. No matter what machine we're on,
- ; we get an exception. If the MMU's in place, we should get a
- ; privilige violation; if not, an F-Line emulation exception.
-
- 2$ move.l (sp)+,d0 ; Get Amiga supplied exception #
- cmpi #11,d0 ; Is it an F-Line?
- beq.s 3$ ; If so, go to the fail routine
- move.l #68851,d0 ; We have MMU
- addq.l #4,2(sp) ; Skip the MMU instruction
- rte
-
- 3$ moveq.l #0,d0 ; It dinna woik,
- addq.l #4,2(sp) ; Skip the MMU instruction
- rte
-
- ;======================================================================
- ;
- ; This function returns the MMU CRP register. It assumes a 68020
- ; system with MMU, or a 68030 based system (eg, test for MMU before
- ; you call this, or you wind up in The Guru Zone). Note that the
- ; CRP register is two longwords long.
- ;
- ; void GetCRP(ULONG *)
- ;
- ;======================================================================
-
- _GetCRP:
- move.l 4(sp),a0 ; Pointer to the CRP storage area
- move.l _AbsExecBase,a6 ; Get ExecBase
- move.l a5,-(sp)
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5
- rts
-
- 2$ pmove crp,(a0)
- rte
-
- ;======================================================================
- ;
- ; This function sets the MMU CRP register. It assumes a 68020
- ; system with MMU, or a 68030 based system (eg, test for MMU before
- ; you call this, or you wind up in The Guru Zone). Note that the
- ; CRP register is two longwords long.
- ;
- ; void SetCRP(ULONG *)
- ;
- ;======================================================================
-
- _SetCRP:
- move.l 4(sp),a0 ; Pointer to the CRP storage area
- move.l _AbsExecBase,a6 ; Get ExecBase
- move.l a5,-(sp)
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5 ; Give back registers
- rts
-
- 2$ pflusha ; explicitly flush the ATC for now
- pmove (a0),crp
- rte
-
- ;======================================================================
- ;
- ; This function returns the MMU TC register. It assumes a 68020
- ; system with MMU, or a 68030 based system (eg, test for MMU before
- ; you call this, or you wind up in The Guru Zone).
- ;
- ; ULONG GetTC()
- ;
- ;======================================================================
-
- _GetTC:
- move.l _AbsExecBase,a6 ; Get ExecBase
- move.l a5,-(sp)
- subq.l #4,sp ; Make a place to dump TC
- move.l sp,a0
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp),d0 ; Here's the result
- addq.l #4,sp
- move.l (sp)+,a5
- rts
-
- 2$ pmove tc,(a0)
- rte
-
- ;======================================================================
- ;
- ; This function sets the MMU TC register. It assumes a 68020
- ; system with MMU, or a 68030 based system (eg, test for MMU before
- ; you call this, or you wind up in The Guru Zone).
- ;
- ; void SetTC(ULONG)
- ;
- ;======================================================================
-
- _SetTC:
- lea 4(sp),a0 ; Get address of our new TC value
- move.l _AbsExecBase,a6 ; Get ExecBase
- move.l a5,-(sp)
- lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5
- rts
-
- 2$ pflusha ; explicitly flush the ATC for now
- pmove (a0),tc
- rte
-
-
- ***********************************************************************
- **
- ** This section contains functions that identify and operate on
- ** FPU things.
- **
- ***********************************************************************
-
- ;======================================================================
- ;
- ; This function returns the type of the FPU in the system as a
- ; longword: 0 (no FPU), 68881, or 68882.
- ;
- ; ULONG GetFPUType();
- ;
- ;======================================================================
-
- _GetFPUType:
- move.l a5,-(sp) ; Save this register
- move.l _AbsExecBase,a6 ; Get ExecBase
- btst.b #AFB_68881,ATNFLGS(a6) ; Does the OS think an FPU is here?
- bne.s 1$
- moveq.l #0,d0 ; No FPU here, dude
- move.l (sp)+,a5 ; Give back the register
- rts
-
- 1$ lea 2$,a5 ; Get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5 ; Give back registers
- rts
-
- 2$ move.l #68881,d0 ; Assume we're a 68881
- fsave -(sp) ; Test and check
- moveq.l #0,d1
- move.b 1(sp),d1 ; Size of this frame
- cmpi #$18,d1
- beq 3$
- move.l #68882,d0 ; It's a 68882
-
- 3$ frestore (sp)+ ; Restore the stack
- rte
-
- ***********************************************************************
- **
- ** Here come the page fault exception handlers
- **
- ***********************************************************************
-
- ;======================================================================
- ;
- ; InsertFaultHandler - trap the system buserr vector (VBR + $
- ;
- ;======================================================================
-
- _InsertFaultHandler:
- move.l a5,-(sp) ; save a5
- move.l _AbsExecBase,a6 ; get ExecBase
- lea 1$,a5 ; get the start of the supervisor code
- CALLSYS Supervisor
- move.l (sp)+,a5 ; restore a5
- rts
-
- 1$ movec VBR,a0 ; get the vector base register
- lea 8(a0),a0 ; BUSERR exception vector
- move.l (a0),_SysBusErrHandler ; save the current bus err handler
- move.l #_HandlePageFault,(a0) ; install ourself
- rte
-
- ;======================================================================
- ;
- ; HandlePageFault - determine whether a bus error was caused by
- ; a page fault, and handle it if it was.
- ; (for now, assume this is a page fault)
- ;
- ;======================================================================
-
- _HandlePageFault:
- movem.l d0-d7/a0-a6,-(sp) ; save registers on system stack
- move.l _AbsExecBase,a6 ; Get ExecBase
- CALLSYS Disable ; just to be sure
- move.l _FastMemHeader,a0 ; allocate a fault node
- move.l #FAULTNODE_SIZE,d0
- CALLSYS Allocate
- tst.l d0 ; did it work?
- bne.s 1$
-
- movem.l (sp)+,d0-d7/a0-a6 ; allocation failed, GURU time!
- 4$ move.l a0,-(sp) ; save a spot on the stack
- move.l a0,-(sp) ; save the register
- move.l _SysBusErrHandler,a0 ; normal bus error
- move.l a0,4(sp) ; set the return address
- move.l (sp)+,a0 ; restore register
- rts ; jump to the big guru error
-
- 1$ move.l d0,a5 ; point at the memory block
- add.l #FAULTNODE_SIZE,d0 ; point to the end of the node
- move.l d0,a4 ; a4 is the fake user stack pointer
-
- lea _PageFaultList,a0 ; where the faults are queued up
- move.l a5,a1 ; this node
- ADDTAIL ; add this FaultNode to the tail of the queue
- addq.w #1,_PendingPageFaults ; count number of faults
-
- lea 8(a5),a3 ; save the registers in the fault node
- moveq #14,d0 ; number of registers - 1
- 2$ move.l (sp)+,(a3)+ ; copy a longword
- dbra d0,2$ ; do it 15 times
-
- move usp,a0 ; get the real user stack pointer
- move.l a0,(a3)+ ; save it
-
- move.l #_RestartTask,-(a4) ; put the fake return address on the stack
- move a4,usp ; fake in the user stack pointer
-
- moveq #0,d0
- move.l d0,a1 ; NULL task name
- CALLSYS FindTask ; find ourselves
- move.l d0,(a3)+ ; save it
-
- moveq #-1,d7 ; don't care which signal
- move.l d7,d0
- CALLSYS AllocSignal ; this is the wake up signal
- cmp.l d0,d7 ; did we get one?
- beq.s 4$ ; nope, GURU time!
- move.l d0,d7 ; save this for later
- move.b d0,(a3)+ ; save the signal number
- addq.l #3,a3 ; padding
-
- move.w SS_VECTOR(sp),d0 ; get the frame vector and type
- andi.w #SS_FORMAT_MASK,d0 ; mask off the format bits
-
- cmpi.w #SSF_FORMAT,d0 ; short?
- bne.s 3$
- moveq #SSF_LSIZE-1,d0 ; size in longwords - 1
- bra.s 5$
-
- 3$ cmpi.w #LSF_FORMAT,d0 ; long?
- bne 4$ ; GURU time again... (not a short branch)
- moveq #LSF_LSIZE-1,d0 ; size in longwords - 1
-
- 5$ move.l (sp)+,(a3)+ ; copy the fault stack frame
- dbra d0,5$
-
- move.w #0,-(sp) ; create a fake exception frame
- lea _LVOSignal(a6),a0 ; where to return to
- move.l a0,-(sp) ; push it
- move sr,d0 ; get the status register
- andi.w #$DFFF,d0 ; clear the supervisor bit
- move.w d0,-(sp) ; push the new status
-
- move.l _PageDaemonTask,a1 ; the daemon to wake
- move.l _PageDaemonSig,d0 ; signal to wake the daemon
- rte ; do it!
-
- ;======================================================================
- ;
- ; RestartTask - restore the state information in the fault node,
- ; free the fault node, and restart the faulted task.
- ;
- ; on entry, a6 -> ExecBase, a5 -> FaultNode, d7 = WakeSigNum
- ;
- ;======================================================================
-
- _RestartTask:
- moveq.l #1,d0
- lsl.l d7,d0 ; signal to wait for
- CALLSYS Wait ; wait till we're paged in
-
- move.l d7,d0 ; we no longer need the signal
- CALLSYS FreeSignal
-
- move.l a5,a4 ; Supervisor clobbers a5
- lea 1$,a5 ; where to continue...
- CALLSYS Supervisor ; drop into supervisor mode
-
- 1$ addq #8,sp ; pop the fake frame from the sys stack
- move.l a4,a5 ; a5 -> FaultNode again
-
- lea FAULT_FRAME(a5),a4 ; point at the fault frame
-
- move.w SS_VECTOR(a4),d0 ; get the frame vector and type
- andi.w #SS_FORMAT_MASK,d0 ; mask off the format bits
-
- cmpi.w #SSF_FORMAT,d0 ; short?
- bne.s 2$
- moveq #SSF_LSIZE-1,d0 ; size in longwords - 1
- lea SSF_SIZE(a4),a4 ; point at the end
- bra.s 3$
-
- 2$ moveq #LSF_LSIZE-1,d0 ; assume long (size in longwords - 1)
- lea LSF_SIZE(a4),a4 ; point at the end
-
- 3$ move.l -(a4),-(sp) ; copy the fault stack frame back
- dbra d0,3$
-
- subq.l #8,a4 ; skip SigNum and Task *
- move.l -(a4),a0 ; real user stack pointer
- move a0,usp ; fix the user stack
-
- moveq #14,d0 ; number of registers - 1
- 4$ move.l -(a4),-(sp) ; copy the saved registers (FPx are ok)
- dbra d0,4$
-
- move.l _FastMemHeader,a0 ; free the fault node (we're unlinked)
- move.l a5,a1 ; the node address
- move.l #FAULTNODE_SIZE,d0 ; how big it is
- CALLSYS Deallocate
-
- pflusha ; flush all ATC registers for now...
- CALLSYS Enable ; turn multitasking back on
- movem.l (sp)+,d0-d7/a0-a6 ; restore the registers
- rte ; and we're off!
-
- end
-