home *** CD-ROM | disk | FTP | other *** search
Text File | 1992-03-22 | 87.3 KB | 1,811 lines |
- COMMENT /
-
- ;This code is Copyright © Nic Wilson 1991, 1992
- ;It is supplied here only as an example of programming
- ;the 68040 MMU on a fully blown 68040 compatible assembler.
- ;such as the one I use, Macro68.
- ;
- ;I am a dealer for Macro68, if anyone is interested in
- ;purchasing this, then please contact me.
- ;
- ;No part of this source code may be used without permission
- ;in writing from Nic Wilson, but i'm easy to talk to so phone or
- ;email me {cbmvax|cbmehq}!cbmaus!wilson!nic@uunet.uu.net
- ;
- ;The source, docs and executable must remain completely unmodified
- ;
- ;I would be grateful if you notify me of any bugs or suggestions
- ;
- ;If you find this source useful as an example when
- ;writing your own then give credit to the author
- ;
- ;NOTE: The macro's used in this source code, are not supplied but
- ;they work in a unique way. All macros are always included but do
- ;not produce object code unless called. When called for the first
- ;time the assembler is forced to change hunk and insert the macro.
- ;The macro call in the main hunk is replaced with a "JSR macro" call,
- ;subsequent calls to the same macro are just replaced with the
- ;"JSR macro". This has benefits, in that code is smaller because
- ;macros are never expanded more than once, and under a debugger
- ;the code looks the same as the source without falling into macro
- ;code that may have been written ages ago. It can then be debugged
- ;without having to see old code. If a large library of routines is
- ;built up this way, it also allows for bug free programming as the
- ;macros will become bug free after a period of time. All this makes
- ;the macros similar to function calls.
- ;All this could be done with a link library, but it is done this way for
- ;sheer speed. This program assembles in under one second, with an
- ;average pass time of .41 seconds.
- ;Try that with a C complier and blink!!
-
- /
-
- INCPATH "includes:"
- MC68040
- strictcomments
- super ;want supervisor ins
- newsyntax ;using new syntax
- exeobj ;want executable file
- strict ;all ins are strict
- objfile "Set040" ;ouptut name
- maclib "commonmac/allmacs.mac" ;pre-assembled macros
- include "commonmac/macs.i" ;macro kludge
-
- SECTION main,CODE ;needed for macros
-
- ;**************************************
- ;The beginning and end of the program.
- ;First we do the startup stuff, parse
- ;the cli command string, get the output
- ;file handle, branch to the main code
- ;on return free it all up and exit
- ;**************************************
-
- pushregs ;save non scratch
- ParseCL ;parse the command line
- FindLibs ;get the libraries
- CALLDOS Output ;get output handle
- move.l d0,(_stdout) ;save it
- bsr.b main ;go do the stuff
- FreeCL ;free cli args
- popregs ;pop the regs
- rts ;bye bye!!
-
- ;************************************************
- ;We check for V2.04, we cannot allow V36 because
- ;this program calls some V37 exec calls. Then we
- ;check if we are using a 68040 CPU.
- ;************************************************
-
- main movea.l (4).w,a6 ;get exec
- cmpi.w #37,(LIB_VERSION,a6) ;check if vers is 2.0x
- blt.w check4kick ;if not check kickrom
- move.w (AttnFlags,a6),d0
- btst #AFB_68040,d0 ;check for 68040
- bne.b found040 ;skip to 040 stuff
-
-
- ;************************************************
- ;If a 68030 is found then the only switch allowed
- ;is the -s for switch to 68040, we check for this
- ;and error if any other switch or none is found.
- ;************************************************
-
- btst #AFB_68030,d0 ;at least 68030 ?
- beq.w cpuerr ;error if not
- tst.l (_argv) ;do we have args
- beq.w cpuerr ;error if not
- movea.l (_argv),a0 ;get the arg array
- movea.l (a0),a0 ;get the first arg
- cmpi.b #'-',(a0)+ ;is it a switch
- bne.w cpuerr ;error if not
- move.b (a0)+,d0 ;get next byte
- bset #5,d0
- cmpi.b #'s',d0 ;is it switch cpu's
- bne.w cpuerr ;error if not
- bra.w doswitch ;go switch 030-040
-
- ;********************************
- ;Check for CLI args, as we only
- ;permit one multiple switch we do
- ;not bother checking for any more
- ;********************************
-
- found040 tst.l (_argv) ;check for CLI args
- beq.w noargs ;skip if none
- movea.l (_argv),a1 ;else get ptr
- movea.l (a1)+,a0 ;get first arg
- move.b (a0)+,d0 ;get byte
- cmpi.b #'?',d0 ;is it usage
- beq.w useprint ;go if so
- cmpi.b #'-',d0 ;else a switch ?
- bne.w noargs ;not valid if not
- move.b (a0)+,d0 ;get next byte
- bset #5,d0 ;set lower case
- cmpi.b #'k',d0 ;is it kickrom
- bne.b notkickrom ;skip if not
- move.l (a1)+,(kickname) ;else get the filename
- bra.w instkick ;and do it
- notkickrom cmpi.b #'f',d0
- bne.w notinst
- argloop move.b (a0)+,d0
- cmpi.b #' ',d0
- ble.w instfast
- cmpi.b #'z',d0 ;is it allow zcaching
- bne.b .notz
- not.b (zcache)
- bra.b argloop
- .notz cmpi.b #'w',d0 ;is mother board space
- bne.b .notw
- not.b (mbspace)
- bra.b argloop
- .notw cmpi.b #'d',d0 ;is it data cache
- bne.b .notd
- clr.w (dcaches)
- move.l #datoff,(datstr)
- bra.b argloop
- .notd cmpi.b #'i',d0 ;is it ins cache
- bne.b .noti
- clr.w (icaches)
- move.l #insoff,(insstr)
- bra.b argloop
- .noti cmpi.b #'t',d0
- bne.b .nott
- not.b (scrtit)
- bra.b argloop
- .nott cmpi.b #'c',d0
- bne.b .notc
- clr.b (z3var1+3)
- clr.b (z3var0+3)
- bra.b argloop
- .notc cmpi.b #'n',d0
- bne.b argloop
- not.b (noclick)
- bra.w argloop
- notinst cmpi.b #'r',d0 ;is it remove
- beq.w removefr ;do it if so
- cmpi.b #'s',d0
- beq.w doswitch
- cmpi.b #'c',d0
- bne.b noargs
- movea.l a0,a2
- maniploop move.b (a2)+,d0
- cmpi.b #' ',d0
- ble.b noargs
- cmpi.b #'I',d0
- beq.w icacheon
- cmpi.b #'i',d0
- beq.w icacheoff
- cmpi.b #'D',d0
- beq.w dcacheon
- cmpi.b #'d',d0
- beq.w dcacheoff
- cmpi.b #'B',d0
- beq.w bcacheon
- cmpi.b #'b',d0
- beq.w bcacheoff
- cmpi.b #'A',d0
- beq.w acacheon
- cmpi.b #'a',d0
- beq.w acacheoff
- cmpi.b #'C',d0
- beq.w con
- cmpi.b #'c',d0
- beq.w coff
-
- ;**********************************
- ;There were no parameters so we
- ;will just display some info unless
- ;we find a CHIPROM setup, in which
- ;case we will go and change it
- ;to FASTROM.
- ;**********************************
-
- noargs lea (credstr,pc),a0 ;our main credits string
- Printf ;print it
- lea (getregs,pc),a5 ;point to supervisor code
- CALLEXEC Supervisor
- move.w d0,(tcreg) ;store tcreg
- move.l d7,(vbreg) ;store vbr
- move.l d5,(it0) ;store itt0 in a var
- move.l d6,(it1) ;store itt1 in a var
- move.l d3,(dt0) ;store dtt0 in a var
- move.l d4,(dt1) ;store dtt1 in a var
- move.l d1,(table1) ;store urp in var
- move.l d1,(urpreg) ;user root pointer
- move.l a0,(srpreg) ;supervisor root pointer
- tst.w d0
- bpl.b .notchiprom
- tst.l (8,a0)
- beq.b .notchiprom
- movea.l (8,a0),a1
- move.l #$80008000,(dcaches)
- move.l (fr_kickmem,a1),d3
- cmpi.l #'KICK',(fr_id,a1)
- beq.w dochipkick
-
- .notchiprom moveq #0,d3 ;clear a reg
- move.l d3,d4 ;and another
-
- tst.w d0 ;test bit 15 of tc reg
- beq.b tcoff ;clear = MMU is off
- tst.l d1 ;test urp
- beq.b putzeros ;zero = all tables clear
- movea.l d1,a0 ;get into address
- move.l (a0),d0 ;get table 2
- clr.b d0 ;clear the descriptor byte
- move.l d0,d3 ;save it
- lea (testcode,pc),a5 ;see if MMU set-up is ours
- CALLEXEC Supervisor
- tst.l d0 ;test result
- beq.b isours
- lea (kickinst,pc),a0
- cmpi.l #'FAST',(fr_id,a4)
- beq.b ourkick
- bmi.b notours ;nope not ours
-
- tcoff clr.l (table1)
- bra.b putzeros
- isours lea (fastinst,pc),a0 ;else get ours string
- ourkick bsr.b fprint ;print it
- notours tst.l d3 ;test table 2
- beq.b putzero ;skip if null
- movea.l d3,a0 ;else get in add reg
- move.l (a0),d0 ;get table 3
- clr.b d0 ;extract address
- move.l d0,d4 ;replace d4
-
- putzeros move.l d3,(table2) ;fill table 2 var
- putzero move.l d4,(table3) ;and table 3 var
- tst.l d2 ;test data cache
- bpl.b printoff ;branch if off
- lea (daton,pc),a0 ;else get on string
- bsr.b fprint ;print it
- bra.b skipoff ;skip off code
- printoff lea (datoff,pc),a0 ;get off code
- bsr.b fprint ;print it
- skipoff tst.w d2 ;test ins cache
- bpl.b printoff1 ;branch if off
- lea (inson,pc),a0 ;else get on string
- bsr.b fprint ;print it
- bra.b skipoff1 ;skip off code
- printoff1 lea (insoff,pc),a0 ;get off string
- bsr.b fprint ;print it
- skipoff1 lea (infostr,pc),a0 ;get rest of info
- lea (table1,pc),a1 ;data for string
- bsr.b fprint ;print it
- lea (usage1,pc),a0 ;info on usage
- bsr.b fprint ;print it
- rts ;we're outa here!!
-
- fprint Printf
- rts
-
- ;***********************************************
- ;The cache manipulation area, all cache modes
- ;are handled here also copyback and writethrough
- ;for the data cache.
- ;bits to change in D0 and the Mask in D1
- ;***********************************************
-
- icacheon moveq #0,d0
- or.l #CACRF_EnableI,d0
- move.l d0,d1
- bra.b docache
-
- icacheoff moveq #0,d0
- move.l d0,d1
- or.l #CACRF_EnableI,d1
- bra.b docache
-
- dcacheon moveq #0,d0
- or.l #CACRF_EnableD,d0
- move.l d0,d1
- bra.b docache
-
- dcacheoff moveq #0,d0
- move.l d0,d1
- or.l #CACRF_EnableD,d1
- bra.b docache
-
- acacheon moveq #0,d0
- or.l #CACRF_EnableI|CACRF_EnableD,d0
- move.l d0,d1
- CALLEXEC CacheControl
- bra.b con
-
- acacheoff moveq #0,d0
- move.l d0,d1
- or.l #CACRF_EnableI|CACRF_EnableD,d1
- CALLEXEC CacheControl
- bra.b coff
-
- bcacheon moveq #0,d0
- or.l #CACRF_EnableI|CACRF_EnableD,d0
- move.l d0,d1
- bra.b docache
-
- bcacheoff moveq #0,d0
- move.l d0,d1
- or.l #CACRF_EnableI|CACRF_EnableD,d1
-
- docache CALLEXEC CacheControl
- dout bra.w maniploop
-
- con lea (getmttx,pc),a5
- CALLEXEC Supervisor
- bset #5,d1
- cmp.l (z3var1,pc),d1
- bne.w testerr
- bset #5,d0
- cmp.l (z3var0,pc),d0
- bne.w testerr
- bra.b cout
-
- coff lea (getmttx,pc),a5
- CALLEXEC Supervisor
- bclr #5,d1
- cmpi.l #$4fbc000,d1
- bne.w testerr
- bclr #5,d0
- cmpi.l #$8f7c000,d0
- bne.w testerr
- cout lea (setdttx,pc),a5
- CALLEXEC Supervisor
- bra.b dout
-
- ;************************************************************
- ;This function is the start of the kickrom code, it allocates
- ;all memory required in one big block in chip ram in the
- ;highest aligned block possible. The MMU set up remaps the
- ;area to $F00000 so that the new kickstart will not see this
- ;chip ram, making our set-up safe through the boot process.
- ;
- ;We allocate the required ram as high as possible by alloc-
- ;ating all of the largest block available, calculating the
- ;end address of this new block, subtracting the required
- ;amount and then lowering this new address to the closest
- ;boundary required. Once we have this new address we give
- ;back the allocated block and AllocAbs the new location.
- ;This is the reason for the Forbid, we cannot allow some
- ;other task to jump in ahead of us and take some ram in
- ;between our alloc, de-alloc and allocabs.
- ;************************************************************
-
- instkick lea (testcode,pc),a5 ;get registers
- CALLEXEC Supervisor ;fetch it
- tst.l d0
- bmi.w mmuerr
- not.b (kickflag) ;set the flag
- JSREXEC Forbid ;multitasking off
- move.l #MEMF_CHIP+MEMF_LARGEST,d1
- JSREXEC AvailMem ;get largest chip
- cmp.l #559592+fr_SIZEOF,d0 ;enough?
- blt.w mem1err ;err if not
- move.l d0,d2 ;save a copy
- move.l #MEMF_CHIP,d1 ;want chip
- JSREXEC AllocMem ;allocate it
- tst.l d0 ;did we?
- beq.w mem1err ;err if not
- move.l d0,-(sp) ;save it
- add.l d2,d0 ;add largest
- subi.l #559592+fr_SIZEOF,d0 ;sub amount required
- andi.l #$ffff8000,d0 ;alignment required
- move.l d2,d1 ;allocated size
- move.l d0,d2 ;new location
- movea.l (sp)+,a1 ;get allocated area
- move.l d1,d0 ;shift size for call
- JSREXEC FreeMem ;free the block
- movea.l d2,a1 ;get new location
- move.l #559592+fr_SIZEOF,d0 ;size needed
- JSREXEC AllocAbs ;allocate it
- move.l d0,(kickmem) ;save ptr
- JSREXEC Permit ;multitasking on
- move.l (kickmem,pc),d0 ;get ptr
- beq.w mem1err ;exit if error
-
- ;********************
- ;Clear this new block
- ;********************
-
- movea.l d0,a0
- addi.l #559592+fr_SIZEOF,d0 ;get the end address
- ..loop clr.w (a0)+ ;clear the whole block
- cmpa.l d0,a0 ;with words, may not be
- blt.b ..loop ;multiples of longs
-
- ;************************************
- ;Set up pointers to each table within
- ;this new block for the kickstart and
- ;ATC entries.
- ;************************************
-
- move.l (kickmem,pc),d0 ;get block start
- addi.l #524288,d0 ;add kickstart size
- move.l d0,(table1) ;table 1
- move.l #512,d1
- add.l d1,d0
- move.l d0,(table2) ;table 2
- add.l d1,d0
- move.l d0,(table3) ;table 3
- addi.l #16384,d0
- move.l d0,(table22) ;2nd table 2
- add.l d1,d0
- move.l d0,(table23) ;2nd table 3
- addi.l #16384,d0 ;get end of table2/3
- movea.l d0,a0 ;our struct
- lea (fr_SIZEOF,a0),a0
- move.l a0,(kickchip)
- lea (crunmmu,pc),a1 ;get the chip code
- lea (crunend,pc),a2 ;and its end
- ..kmloop move.w (a1)+,(a0)+ ;move it to chip
- cmpa.l a2,a1 ;until finished
- bne.b ..kmloop
- bra.w gotkick
-
- ;**************************
- ;OK so we have to install
- ;FASTROM, but first we make
- ;sure that the MMU isn't
- ;already in use
- ;**************************
-
- instfast lea (getregs,pc),a5 ;get registers
- CALLEXEC Supervisor ;fetch it
- tst.w d0 ;is it enabled
- bpl.b mmuok ;no its disabled
- tst.l d1 ;test urp reg
- beq.b .mmuerr ;exit (saves a reloc)
- lsr.l #1,d1 ;make sure its even
- add.l d1,d1 ;quicker than lsl.l
- movea.l d1,a0
- movea.l (8,a0),a0 ;get third ptr
- cmpi.l #'NICS',(fr_id,a0) ;is it our fastrom
- beq.w ourfastrom
- .mmuerr bra.w mmuerr
-
-
- ;************************************
- ;Now we allocate 512k of memory
- ;aligned on a 8k boundary this is
- ;handled by my AllocAligned macro and
- ;it will clear the block if the
- ;MEMF_CLEAR attribute is set. It will
- ;return an aligned block according to
- ;the value in D2
- ;************************************
-
- mmuok move.l #524288,d0 ;512k size
- move.l #MEMF_FAST,d1 ;clear not required
- move.l #32768,d2 ;32k boundary
- AllocAligned
- tst.l d0 ;did we get it
- beq.w mem1err ;exit if not
- move.l d0,(kickmem) ;save the ptr
-
- ;***********************
- ;Now we allocate memory
- ;for the first table
- ;***********************
-
- move.l #512,d3 ;we'll use this more
- move.l d3,d0 ;size of table1
- move.l #MEMF_FAST+MEMF_CLEAR,d1 ;we want fast & clear
- move.l d3,d2 ;512 byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem2err ;exit if not
- move.l d0,(table1) ;save it
-
- ;**********************
- ;Now we allocate memory
- ;for the second table
- ;**********************
-
- move.l d3,d0 ;size of table2
- move.l #MEMF_FAST+MEMF_CLEAR,d1 ;we want fast & clear
- move.l d3,d2 ;512 byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem3err ;exit if not
- move.l d0,(table2) ;save it
-
- ;**********************
- ;Now we allocate memory
- ;for the third table
- ;**********************
-
- move.l #16384,d0 ;size of table3
- move.l #MEMF_FAST+MEMF_CLEAR,d1 ;fast and clear
- move.l d3,d2 ;512 byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem4err ;exit if not
- move.l d0,(table3) ;save it
-
- ;**************************
- ;Now we allocate memory for
- ;the second-second table
- ;**************************
-
- move.l d3,d0 ;size of table2-2
- move.l #MEMF_FAST+MEMF_CLEAR,d1 ;we want fast & clear
- move.l d3,d2 ;512 byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem5err ;exit if not
- move.l d0,(table22) ;save it
-
- ;**************************
- ;Now we allocate memory for
- ;the second-third table
- ;**************************
-
- move.l #16384,d0 ;size of table3
- move.l #MEMF_FAST+MEMF_CLEAR,d1 ;fast and clear
- move.l d3,d2 ;512 byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem6err ;exit if not
- move.l d0,(table23) ;save it
-
- ;****************************************
- ;Now we allocate a structure to hold
- ;all the old values so we can remove all
- ;this if asked to this will be linked on
- ;to an invalid entry in table 1 so we
- ;can retreive it later if needed
- ;***************************************
-
- move.l #fr_SIZEOF,d0 ;size of struct
- move.l #MEMF_FAST,d1 ;fast
- move.l #32768,d2 ;32k byte boundary
- AllocAligned ;get it
- tst.l d0 ;did we?
- beq.w mem7err ;exit if not
- gotkick movea.l d0,a4
- move.l d0,(fr_struct,a4) ;save it
- move.l (table23,pc),(fr_table5,a4)
- move.l (table22,pc),(fr_table4,a4)
- move.l (table3,pc),(fr_table3,a4)
- move.l (table2,pc),(fr_table2,a4)
- move.l (table1,pc),(fr_table1,a4)
- move.l (kickmem,pc),(fr_kickmem,a4)
- move.l #'NICS',(fr_id,a4) ;our id
-
- ;******************************************************************
- ;If we're kickromming we check the supplied filename, if a floppy
- ;drive only we read the disk to see if its a valid kickstart disk,
- ;if no disk is found we bring up a requester and ask for one,
- ;else we check to see if its an old kickstart or superkickstart.
- ;If superkickstart we bring up a requester asking if they want
- ;kick 1.3 or v2.0. If the filename is a pointer to a file we
- ;load that file check if its a 256k kick or 512k kick and set it up
- ;******************************************************************
-
- tst.b (kickflag,pc) ;check the flag
- bpl.w notkick ;skip if not kickrom
-
- move.l #'KICK',(fr_id,a4) ;change the id
- movea.l (kickname,pc),a0 ;get the filename
- move.b (a0)+,d0 ;get first byte
- bset #5,d0 ;set for lower case
- cmpi.b #'d',d0 ;is it a d
- bne.w notrack ;not trackdisk if not
- move.b (a0)+,d0 ;get next byte
- bset #5,d0 ;lower case
- cmpi.b #'f',d0 ;is it an f
- bne.w notrack ;not trackdisk if not
- move.b (a0)+,d0 ;get next byte
- cmpi.b #$30,d0 ;is it in range
- blt.w notrack ;skip if not
- cmpi.b #$33,d0 ;check upper range
- bgt.w notrack ;skip if not
- move.b (a0),d0 ;get next byte
- cmpi.b #':',d0 ;is it a colon
- bne.w notrack ;skip if not
- movea.l (kickname,pc),a0 ;get the name
- tst.b (4,a0) ;is it null terminated
- bne.w notrack ;skip out if not
- InitDrive ;initialise the drive
- tst.l d0 ;test result
- ble.w kickerr ;end if error
- move.l d1,(ioreq) ;save the iorequest
- .testdisk movea.l (ioreq,pc),a1
- DiskIn
- tst.l d0
- beq.b .diskisin
- lea (easyreq,pc),a0 ;else get easy struct
- move.l #diskgads,(es_GadgetFormat,a0) ;change the gadgets
- move.l #disktext,(es_TextFormat,a0) ;and the the text
- move.l #DISKINSERTED,(esidcmp)
- move.l #kickname,d0 ;data
- bsr.w requester ;do the requester
- tst.l d0 ;check their answer
- beq.w kickabort ;they want kick 2.0
- bra.b .testdisk
- .diskisin movea.l (kickmem,pc),a0 ;get the buffer
- movea.l (ioreq,pc),a1 ;and the ioreq
- moveq #0,d0 ;offset 'bootblock'
- move.l #TD_SECTOR*2,d1 ;two sectors
- ReadBlocks ;read it
- bsr.w motoroff
- tst.l d0 ;check result
- bne.w kick1err ;end if error
- movea.l (kickmem,pc),a0 ;get buffer
- cmpi.l #'KICK',(a0) ;check if kickstart
- bne.w kick1err ;end if not
- cmpi.l #'SUP0',(4,a0) ;check super
- bne.b notsuper ;skip if not
- lea (easyreq,pc),a0 ;else get easy struct
- move.l #eskickgads,(es_GadgetFormat,a0) ;change the gadgets
- move.l #eskick,(es_TextFormat,a0) ;and the the text
- moveq #0,d0 ;no data
- move.l d0,(esidcmp) ;clear idcmp
- bsr.w requester ;do the requester
- tst.l d0 ;check their answer
- beq.b kick2.0 ;they want kick 2.0
- move.l #$400,d0 ;offset for 1.3 super
- bra.b loadkick ;and go load it
- kick2.0 move.l #$40400,d0 ;offset for 2.0 super
- move.l #$80000,d1 ;512k length
- movea.l (kickmem,pc),a0 ;get buffer
- bra.b load2.0 ;and go load it
- notsuper move.l #$200,d0 ;offset for 1.3 normal
- loadkick movea.l (kickmem,pc),a0 ;get buffer
- lea ($40000,a0),a0 ;add 256k for 1.3
- move.l #$40000,d1 ;and 256k as length
- load2.0 movea.l (ioreq,pc),a1 ;get it requester
- ReadBlocks ;read the data
- bsr.b motoroff
- tst.l d0 ;test result
- bne.w kick1err ;end if error
- movea.l (ioreq,pc),a1 ;get ioreq
- ExitDrive ;un-init the drive
- bra.b endtrack ;and skip file part
-
- motoroff move.l d0,-(sp)
- movea.l (ioreq,pc),a1
- MotorOff
- move.l (sp)+,d0
- rts
-
- notrack movea.l (kickname,pc),a1 ;get the name
- movea.l (kickmem,pc),a0 ;and the buffer
- moveq #4,d0 ;want 4 bytes
- ReadFile ;read it
- movea.l (kickname,pc),a1 ;get the name
- movea.l (kickmem,pc),a0 ;and the buffer
- cmpi.w #$1111,(a0) ;what type of kick
- beq.s dosmall ;is a 256k kick
- cmpi.w #$1114,(a0) ;else is it 512k
- bne.w kickfilerr ;end if not kickstart
- move.l #524288,d0 ;else set size
- bra.b dobig ;and go get it
-
- dosmall clr.l (a0) ;clear the kick id
- lea ($40000,a0),a0 ;add 256k to 1.3 buffer
- move.l #262144,d0 ;and its size
- dobig ReadFile ;read the data
- endtrack movea.l (kickmem,pc),a0
- cmpi.w #$1114,(a0)+ ;is it 2.0
- bne.w not2.0 ;skip if not
- lea (patch,pc),a0 ;else tell we're patching
- Printf
- movea.l (kickmem,pc),a1 ;get buffer
- lea ($7ffff,a1),a1 ;get end address
-
- ;**************************************************
- ;This next part scans through a V2.0x kickstart and
- ;patches out any 68040 MMU instructions that would
- ;corrupt our set up. Each one found is converted
- ;into a 'nop' instruction.
- ;**************************************************
-
-
- movea.l (kickmem,pc),a0 ;get buffer
- .loop cmpa.l a1,a0 ;are we finsihed
- bgt.w not2.0 ;exit if so
- cmpi.w #$4e7b,(a0)+ ;look for movec
- bne.b .loop ;loop to find
-
- move.b (1,a0),d0 ;if next byte less than
- cmpi.b #3,d0 ;3 we're not interested
- blt.b .loop ;so loop back
- cmpi.b #7,d0 ;if it is greater than
- bgt.b .loop ;7 we're not interested
- moveq #$f,d0
- and.b (a0),d0 ;test bits 0-3 if >0
- bne.b .loop ;we're not interested
- move.w #$4e71,(-2,a0) ;OK so we've got an MMU
- move.w #$4e71,(a0)+ ;instruction so nop'em
- bra.b .loop ;and loop
-
- ;*******************************************
- ;Once all the above mods are made we correct
- ;the checksum of the kickstart
- ;*******************************************
-
- not2.0 movea.l (kickmem,pc),a0
- movea.l a0,a1
- lea ($7ffe8,a0),a0
- moveq #0,d5
- move.l d5,(a0) ;clear checksum
- moveq #-1,d1
- moveq #1,d2
- .oneloop add.l (a1)+,d5
- bcc.b .csloop
- addq.l #1,d5
- .csloop dbf d1,.oneloop
- dbf d2,.oneloop
- moveq #-1,d0
- sub.l d5,d1
- move.l d1,(a0)
- CALLEXEC CacheClearU ;flush the changes
- bra.w skipclick
-
- ;**************************************************
- ;Now we copy the ROM image, that's the beauty of
- ;assembler, we can take advantage of the efficiency
- ;of the MOVE16 instruction. C programmers have no
- ;idea, they call CopyMemQuick and hope for the
- ;best!! Plus it saves us from having to flush
- ;the cache as MOVE16 instruction prevents the
- ;data from being cached and invalidates any entry
- ;in the cache.
- ;**************************************************
-
- notkick move.l #$7fff,d0 ;(512k/16)-1 loop count
- lea ($f80000),a0 ;ROM kickstart address
- movea.l (kickmem,pc),a1 ;destination
- ..turbocopy move16 (a0)+,(a1)+ ;16 bytes at a time
- dbf d0,..turbocopy ;loop till done
-
- ;***************************************
- ;This will change the Workbench screen
- ;title to Amiga FastBench if the command
- ;line option allows it.
- ;***************************************
-
- lookbyte tst.b (scrtit,pc)
- bmi.b skiptit
- subq.l #1,a1
- cmpi.b #'W',-(a1)
- bne.b lookbyte
- cmpi.b #'o',(1,a1)
- bne.b lookbyte
- cmpi.b #'r',(2,a1)
- bne.b lookbyte
- cmpi.b #'k',(3,a1)
- bne.b lookbyte
- cmpi.b #' ',(-1,a1)
- bne.b lookbyte
- cmpi.b #'a',(-2,a1)
- bne.b lookbyte
- move.b #'F',(a1)+
- move.b #'a',(a1)+
- move.b #'s',(a1)+
- move.b #'t',(a1)+
-
- ;***********************************************
- ;This will patch the kickstart to stop drives
- ;from clicking if the command line option allows
- ;it
- ;***********************************************
-
- skiptit tst.b (noclick,pc)
- beq.b skipclick
- movea.l (4).w,a0
- lea (DeviceList,a0),a0
- lea (tdname,pc),a1
- CALLEXEC FindName
- tst.l d0
- beq.b skipclick
- movea.l d0,a0
- movea.l (LN_NAME,a0),a0
- .look6b cmpi.b #$6b,(a0)+ ;find bchg instruction
- bne.b .look6b
- tst.b (a0)+ ;2nd byte of instruction
- bne.b .look6b
- cmpi.b #1,(a0)+ ;is it the one we want
- bne.b .look6b ;nope! keep looking
- suba.l #$f80003,a0 ;calculate offset value
- adda.l (kickmem,pc),a0 ;add new start address
- move.b #$eb,(a0) ;change it to bset
-
-
- ;**************************************************
- ;place the pointer to the second table in the first
- ;and 'OR' in the descriptor type the rest are set
- ;as invalid but we link our structure of old values
- ;onto an invalid descriptor.
- ;**************************************************
-
- skipclick movea.l (table1,pc),a0 ;get first table
- move.l (table2,pc),d0 ;get second table
- or.b #3,d0 ;UDT descriptor
- move.l d0,(a0)+ ;shove it in
- move.l (table22,pc),d0 ;get 2nd table 2
- or.b #3,d0 ;UDT descriptor
- move.l d0,(a0)+ ;shove it in
- move.l a4,(a0) ;link our struct on
- ;invalid entry UDT=0
- ;****************************************************
- ;Now we set-up table 2, 128 pointers to table3 entries
- ;and descriptor type 'ORed' in.
- ;****************************************************
-
- movea.l (table2,pc),a0 ;get table 2
- move.l (table3,pc),d2 ;get table 3
- moveq #127,d0 ;128 entries
- or.l #3,d2 ;UDT descriptor
- dotable2 move.l d2,(a0)+ ;move one in
- addi.l #128,d2 ;add next address
- dbf d0,dotable2 ;loop till done
-
- ;******************************************
- ;Addresses from $0 up to $f7ffff marked as
- ;global, non-cachable serialized
- ;******************************************
-
- movea.l (table3,pc),a0
- move.l #$441,d1
- move.l #1983,d0
- dotable32 move.l d1,(a0)+
- addi.l #$2000,d1
- dbf d0,dotable32
-
- ;**********************************************
- ;If kickrom, this will map the Chip memory area
- ;we allocated as $F00000 - $FFFFFF to fool the
- ;kickstart as to the size of chip memory
- ;**********************************************
-
- tst.b (kickflag,pc)
- beq.b skipk
- movea.l (table3,pc),a1
- move.l (kickmem,pc),d0
- moveq #11,d1
- lsr.l d1,d0
- lea (a1,d0.l),a1
- move.l #$f00000,d1
- sub.l (kickmem,pc),d1
- moveq #63,d0
- dokickm add.l d1,(a1)+
- dbf d0,dokickm
-
- ;**********************************************
- ;If allowed by the CLI switch this will map the
- ;ZorroII memory area $200000 - $A00000 as
- ;cachable copyback
- ;**********************************************
-
- skipk tst.b (zcache,pc)
- beq.b skipz
- movea.l (table3,pc),a1
- lea ($400,a1),a1
- move.l #1023,d0
- move.b #$21,d1
- dozorro move.b d1,(3,a1)
- dbf d0,dozorro
-
- ;*************************************************
- ;the rest of table 3 for the kickstart remap
- ;64 entries mapping 8k each, and write protected
- ;*************************************************
-
- skipz moveq #63,d0
- move.l (kickmem,pc),d1
- or.l #$405,d1
- dotable33 move.l d1,(a0)+
- addi.l #$2000,d1
- dbf d0,dotable33
-
- ;*********************************************
- ;The second 16MB/256k segments are mapped here
- ;each entry maps 8k of the 256k making a total
- ;of 32 per 256k & 64 of these map the 16MB
- ;These are set for Data Cachable Copyback as
- ;memory on some boards will reside here but an
- ;optional cli flag allows this to be changed
- ;to writethrough
- ;*********************************************
-
- move.l #2047,d0
- move.l #$1000421,d1
- tst.b (mbspace,pc)
- beq.b dotable34
- bclr #5,d1
- dotable34 move.l d1,(a0)+
- addi.l #$2000,d1
- dbf d0,dotable34
-
- ;******************************************************
- ;Now we set-up table 2 for the second 32 Meg address
- ;space, 128 pointers to table3 entries and descriptor
- ;type 'ORed' in. Each table3 entry controls 8k of
- ;the 256k of each table 2 entry, each is a long word
- ;so the address increment value is 32*4 = 128 as shown.
- ;******************************************************
-
- movea.l (table22,pc),a0
- move.l (table23,pc),d2
- moveq #127,d0
- or.l #3,d2
- dotable22 move.l d2,(a0)+
- addi.l #128,d2
- dbf d0,dotable22
-
- ;**************************************************************
- ;and now table 3 number 2. This maps each of the 256k segments
- ;in table 2 above with 32 8k page descriptors.
- ;**************************************************************
-
- movea.l (table23,pc),a0
- move.l #$2000421,d1
- move.l #4095,d0
- tst.b (mbspace,pc)
- beq.b dotable23
- bclr #5,d1
- dotable23 move.l d1,(a0)+
- addi.l #$2000,d1
- dbf d0,dotable23
-
- ;***********************************
- ;We save the old transparent values
- ;straight into our structure that is
- ;tagged on to an invalid entry.
- ;A4 points to the table.
- ;***********************************
-
- lea (getmttx,pc),a5
- CALLEXEC Supervisor
- move.l d0,(fr_dtt0,a4)
- move.l d1,(fr_dtt1,a4)
- move.l d2,(fr_itt0,a4)
- move.l d3,(fr_itt1,a4)
-
- ;***********************************************************
- ;ZorroIII Memory expansion space is set for Data Cachable
- ;Copyback and the ZorroIII Expansion space is invalid at
- ;the moment.
- ;This is all done in the Transparent Translation
- ;instruction and data registers.
- ;When setting all this up we do as much as we can without
- ;being disabled. We can only disable for a very short
- ;period of time, so there is no need to be disabled for
- ;the entire installation. The Transparent settings will
- ;take effect immediately but thats ok too! We only need
- ;be disabled for turning the MMU on.
- ;
- ;
- ;OK, now the magic stuff. Stick in the keys, clean out the
- ;carby, give a couple of pumps, and a bit of choke and lets
- ;see if she'll start.
- ;***********************************************************
-
- move.l (table1,pc),d3 ;get table start
- move.l (z3var0,pc),d6 ;copyback up to $0FFFFFFF
- move.l (z3var1,pc),d4 ;copyback up to $07FFFFFF
- move.w #$c000,(tcreg)
- move.l (table1,pc),(urpreg)
- move.l (table1,pc),(srpreg)
- move.l d4,(dt1) ;save for printing
- move.l d6,(dt0) ;save for printing
- move.l #$c040,d5
- tst.b (kickflag,pc)
- bmi.b .leaveon
- moveq #0,d0 ;d0 = cache bits
- move.l d0,d1 ;clear d1
- or.l #CACRF_EnableI|CACRF_EnableD,d1 ;ins & data caches mask
- CALLEXEC CacheControl ;turn 'em both off
- bsr.w flushcaches ;flush the caches
- .leaveon moveq #0,d2 ;need a clear reg
- lea (setmmu,pc),a5 ;set-up some of the regs
- JSREXEC Supervisor
- move.l d0,(vbreg)
- JSREXEC Disable ;really selfish!!
- lea (magic,pc),a5 ;turn this all on
- JSREXEC Supervisor
- JSREXEC Enable
- move.l d4,(it1) ;save for printing
- move.l d5,(it0) ;save for printing
- lea (fastinst,pc),a0 ;finsihed string
- bra.w printit ;we're outa here
-
-
- setmmu movec d2,tc ;make sure the MMU is off
- nop
- pflusha ;invalidate all ATC entries
- nop
- movec d3,urp ;set the user root pointer
- movec d3,srp ;and the supervisor one
- movec d4,dtt1 ;set the data trans' reg
- movec d5,dtt0 ;control the lowest 16MB
- move.l #$8f7c000,d5
- move.l #$4fbc000,d4
- movec d4,itt1 ;and set the itt1 reg
- movec d5,itt0 ;and the itt0 reg
- movec vbr,d0
- rte
-
- magic tst.b (kickflag,pc)
- bmi.b notfast
- move.w #$c000,d2 ;set for MMU on with 8k pages
- movec d2,tc ;IGNITION...
- movec d6,dtt0 ;set dtt0 for ZorroIII control
- move.l (dcaches,pc),d0 ;requested cache settings
- movec d0,cacr ;and do it
- rte ;I can smell the rubber..
- notfast move.l #$80008000,d0
- movec d0,cacr
- lea (crunjmp,pc),a0
- moveq #0,d3
- lea (crun,pc),a6
- crunloop jmp (a6)
- crunit reset
- reset
- crun move.w ($dff010),d0 ;read something
- subq.l #1,d3
- bpl.b crun
- move.b #3,($bfe201)
- move.b #2,($bfe001)
- cmpa.l a0,a6
- beq.b crunloop
- movea.l a0,a6
- move.l #400,d3
- bra.b crunit
-
- crunjmp movea.l (kickchip,pc),a0
- lea ($f80002),a2
- movea.l (kickmem,pc),a1
- cmpi.w #$1114,(a1)
- beq.b crungo
- lea ($fc0002),a2
- crungo jmp (a0)
-
- crunmmu movea.l (4).w,a0
- movea.l a0,a1
- lea ($2000,a1),a1
- ..loop clr.l (a0)+
- cmpa.l a0,a1
- bge.b ..loop
- moveq #0,d0
- move.l d0,(4).w
- move.l d0,(0).w
- movec d0,cacr
- movec d0,tc
- nop
- cpusha bc
- cinva bc
- pflusha
- nop
- moveq #19,d0
- .loopled move.l #$3fff,d1
- bchg #1,($bfe001)
- .led dbf d1,.led
- dbf d0,.loopled
- move.l #$c000,d0
- movec d0,tc
- movec d6,dtt0
- jmp (a2)
- nop
- nop
- crunend nop
-
- ;************************
- ;Return various registers
- ;************************
-
- getregs movec tc,d0 ;traslation control
- movec urp,d1 ;user root pointer
- movec cacr,d2 ;cache control register
- movec dtt0,d3 ;data transparaent translation 0
- movec dtt1,d4 ;data transparaent translation 1
- movec itt0,d5 ;ins transparaent translation 0
- movec itt1,d6 ;ins transparaent translation 1
- movec vbr,d7
- movec srp,a0
- rte
-
- flushcaches suba.l a0,a0 ;clear a0
- moveq #-1,d0 ;length = all
- moveq #0,d1 ;clear d1
- or.l #CACRF_ClearI|CACRF_ClearD,d1 ;both ins & data
- JMPEXEC CacheClearE ;flush 'em
-
-
- getmttx movec dtt0,d0
- movec dtt1,d1
- movec itt0,d2
- movec itt1,d3
- rte
-
- ;*********************************************************
- ;This routine will test if the MMU set-up is ours, if so
- ;it will extract our structure from the invalid descriptor
- ;and remove the MMU set-up, restore it the way it was and
- ;free up all the resources.
- ;*********************************************************
-
- removefr lea (testcode,pc),a5 ;go and see if MMU is ours
- CALLEXEC Supervisor
- tst.l d0 ;is it? (struct returned in a4)
- beq.b .oursison
- bpl.w prnorom
- cmpi.l #'FAST',(fr_id,a4)
- beq.w remerr
- bra.w testerr
- .oursison move.l (fr_dtt0,a4),d2 ;get old dtt0 value
- move.l (fr_dtt1,a4),d3 ;get old dtt1 value
- move.l (fr_itt0,a4),d4 ;get old itt0 value
- move.l (fr_itt1,a4),d5 ;get old itt1 value
- moveq #0,d0 ;se the bits as off
- move.l d0,d1 ;clear the mask
- or.l #CACRF_EnableI|CACRF_EnableD,d1 ;set the mask bits
- CALLEXEC CacheControl ;turn them off
- bsr.w flushcaches ;and flush 'em
- lea (restoremmu,pc),a5 ;replace old values
- JSREXEC Supervisor
- JSREXEC Disable ;shut down till fastrom is gone!
- lea (removemmu,pc),a5 ;go remove MMU set-up
- JSREXEC Supervisor
- JSREXEC Enable ;all OK if we're still here
- move.l (fr_table1,a4),(table1)
- move.l (fr_table2,a4),(table2)
- move.l (fr_table3,a4),(table3)
- move.l (fr_table4,a4),(table22)
- move.l (fr_table5,a4),(table23)
- move.l (fr_kickmem,a4),(kickmem)
- bsr.w freetab6 ;go free all memory
- moveq #0,d0 ;se the bits as off
- or.l #CACRF_EnableI|CACRF_EnableD,d0 ;set the mask bits
- move.l d0,d1 ;clear the mask
- CALLEXEC CacheControl ;turn them on
- move.l #remstr,-(sp) ;tell 'em we removed it OK
- printstr lea (credstr,pc),a0 ;print the credits
- Printf
- bra.w nobuff ;bye bye
-
- ;*********************
- ;Print kickrom aborted
- ;*********************
-
- kickabort move.l #opabo,-(sp)
- bra.b freedr
-
- ;*************************
- ;Print error opening drive
- ;*************************
-
- kickfilerr move.l #notkickf,-(sp)
- bra.b freeabs
-
- ;*************************
- ;Print error opening drive
- ;*************************
-
- kickerr move.l #baddrive,-(sp)
- bra.b freeabs
-
- ;*********************
- ;Print disk read error
- ;*********************
-
- kick1err move.l #readerr,-(sp)
- freedr movea.l (ioreq,pc),a1
- ExitDrive
- freeabs move.l #559592+fr_SIZEOF,d0 ;total size alloced
- movea.l (kickmem,pc),a1
- CALLEXEC FreeMem
- bra.b printstr
-
- ;********************
- ;Print cannot kickrom
- ;********************
-
- remerr move.l #badkick,-(sp)
- bra.b printstr
-
- ;**********************************
- ;Print credits and unkown mmu setup
- ;**********************************
-
- testerr move.l #unkmmu,-(sp)
- bra.b printstr
-
- ;***************************************
- ;Print credits and cannot remove fastrom
- ;***************************************
-
- prnorom move.l #norom,-(sp)
- bra.w printstr
-
- ;***********************
- ;Print credits and usage
- ;***********************
-
- useprint move.l #usage,-(sp)
- bra.w printstr
-
- ;************************************************
- ;Print credits and error if no PP&S card is found
- ;************************************************
-
- perr move.l #ppserr,-(sp)
- bra.w printstr
-
- ;************************************
- ;This will turn the FASTROM settings
- ;off and restore all as it was before
- ;we changed it
- ;It is done in two sections because
- ;some of it does not need to be done
- ;on a disable and the other should.
- ;************************************
-
- removemmu moveq #0,d0
- pflusha
- movec d0,tc
- rte
-
- restoremmu movec d2,dtt0
- movec d3,dtt1
- movec d4,itt0
- movec d5,itt1
- movec d0,urp
- movec d0,srp
- rte
-
- ;***********************************************
- ;Check if the urp register is pointing to
- ;our FASTROM table or something else and
- ;return the result
- ;INPUT = none RESULT = 0 our fastrom installed
- ; 1 if MMU not on
- ; -1 MMU on but not ours
- ;***********************************************
-
- testcode movec tc,d0 ;get tc reg
- tst.w d0 ;is MMU on?
- beq.b tc_err1 ;nope! branch
- movec urp,d0 ;else get urp reg
- beq.b tc_err ;exit if NULL
- movea.l d0,a4
- move.l (8,a4),d0 ;get third entry
- beq.b tc_err ;not ours if NULL
- movea.l d0,a4
- cmpi.l #'NICS',(fr_id,a4) ;check for our ID
- bne.b tc_err ;not ours
- moveq #0,d0 ;else set as ours
- rte
- tc_err moveq #-1,d0
- rte
- tc_err1 moveq #1,d0
- rte
-
- ;**********************
- ;Set the dttx registers
- ;**********************
-
- setdttx movec d0,dtt0
- movec d1,dtt1
- rte
-
- ;**********************************************
- ;Free memory routines for removal of FASTROM or
- ;partial freeing if memory error on installing
- ;**********************************************
-
- freetab6 movea.l (fr_struct,a4),a1
- move.l #fr_SIZEOF,d0
- bsr.b freeit
- freetab5 movea.l (table23,pc),a1
- move.l #16384,d0
- bsr.b freeit
- freetab4 movea.l (table22,pc),a1
- move.l #512,d0
- bsr.b freeit
- freetab3 movea.l (table3,pc),a1
- move.l #16384,d0
- bsr.b freeit
- freetab2 movea.l (table2,pc),a1
- move.l #512,d0
- bsr.b freeit
- freetab1 movea.l (table1,pc),a1
- move.l #512,d0
- bsr.b freeit
- freekick movea.l (kickmem,pc),a1
- move.l #524288,d0
- freeit CALLEXEC FreeMem
- rts
-
- ;**********************************
- ;Error string handling and printing
- ;**********************************
-
- mem7err lea (strstruct,pc),a0
- bsr.b dofree
- bra.b freetab5
-
- mem6err bsr.b dotrans
- bra.b freetab4
-
- mem5err bsr.b dotrans
- bra.b freetab3
-
- mem4err bsr.b dotrans
- bra.b freetab2
-
- mem3err bsr.b dotrans
- bra.b freetab1
-
- mem2err bsr.b dotrans
- bra.b freekick
-
- mem1err lea (strkick,pc),a0
-
- dofree move.l a0,-(sp)
- lea (memstr,pc),a0
- bsr.b steprintf
- movea.l (sp)+,a0
- bra.b printit
-
- dotrans lea (strtrans,pc),a0
- bsr.b dofree
- rts
-
- steprintf Printf
- rts
-
- ourfastrom lea (ourrom,pc),a0
- bra.b printit
-
- mmuerr lea (mmustr,pc),a0
- bra.b printit
- cpuerr lea (cpustr,pc),a0
- bra.b printit
-
- vererr lea (verstr,pc),a0
- printit move.l a0,-(sp)
- lea (credstr,pc),a0
- bsr.b steprintf
- tst.l (table1,pc)
- beq.b nobuff
- lea (kickstr,pc),a0
- lea (kickmem,pc),a1
- bsr.b steprintf
- lea (infostr,pc),a0
- lea (table1,pc),a1
- bsr.b steprintf
- movea.l (datstr,pc),a0
- bsr.b steprintf
- movea.l (insstr,pc),a0
- bsr.b steprintf
- nobuff move.l (sp),d0
- cmp.l #unkmmu,d0
- blt.b .skip
- cmp.l #memstr,d0
- bgt.b .skip
- lea (error,pc),a0
- bsr steprintf
- .skip movea.l (sp)+,a0
- bra steprintf
-
-
- ;************************************************************
- ;We have to be careful here, we came here if we have found
- ;that we are not running under 2.0x. We maybe illegal but
- ;we might also be a kick'ed rom 1.3 or 1.2 and they are
- ;asking us to do a FASTROM. Firstly exec probably is not
- ;aware of the 68040. We make sure we have a 68040 then we
- ;will check the MMU set up for our magic kickrom id. As we
- ;need the mmu urp register, and that instruction is 68040
- ;specific, we may aswell use that to test for 68040 presence.
- ;The movec instruction will always except to the trap code
- ;but if we are on a 68040 the exception will be a privilege
- ;violation else it will be an illegal instruction.
- ;If all is OK, we copy the entire kickstart and atc entries
- ;over into an allocated fast ram area, then modify the
- ;necessary atc entries for this new ram area, kill the
- ;current set up, turn on the new one and add the used chip
- ;memory to the meg boundary to exec.
- ;************************************************************
-
- check4kick move.l #$8000,(dcaches)
- movea.l (_TaskBlock),a0 ;get our task
- move.l (TC_TRAPCODE,a0),-(sp) ;save trap code
- move.l #test040,(TC_TRAPCODE,a0) ;patch ours in
- movec urp,d0 ;do 68040 instruction
- move.l (sp)+,(TC_TRAPCODE,a0) ;replace trap code
- tst.l d0 ;test result
- beq.w vererr ;error, we're illegal
- tst.w d1 ;check if MMU is on
- bpl.w vererr ;if not we're illegal
- movea.l (4).w,a6 ;get execbase
- move.w (AttnFlags,a6),d1 ;get the attn flags
- bset #AFB_68040,d1 ;set for 68040
- bset #AFB_FPU40,d1 ;set for 040 FPU
- bset #AFB_68030,d1 ;and for 68030
- move.w d1,(AttnFlags,a6) ;and put back
- movea.l d0,a0 ;make a copy of urp
- tst.l (8,a0) ;test for a third ptr
- beq.w vererr ;skip if null
- movea.l (8,a0),a0 ;else get third ptr
- cmpi.l #'KICK',(fr_id,a0) ;look for our id
- bne.w vererr ;skip out if not kickrom
- move.l (fr_kickmem,a0),d3
- dochipkick move.l #559592+fr_SIZEOF,d0 ;total size needed
- move.l #MEMF_FAST,d1 ;need fast memory
- move.l #32768,d2 ;32k boundary
- AllocAligned ;get aligned memory
- tst.l d0 ;test result
- beq.w mem1err ;out on error
- move.l d0,(kickmem) ;we just put it there
- movea.l d0,a1 ;copy dest ram
- move.l #$7fff,d0 ;(512k/16)-1 loop count
- lea ($f80000),a0 ;ROM kickstart address
- ..turbocopy move16 (a0)+,(a1)+ ;16 bytes at a time
- dbf d0,..turbocopy ;loop till done
-
- move.l #35304+fr_SIZEOF,d0 ;remainder (-512k)
- movea.l d3,a0
- lea ($80000,a0),a0
- movea.l a0,a2 ;make a copy
- lea (a2,d0.l),a2 ;calc end address
- movea.l (kickmem,pc),a1 ;get new block
- lea ($80000,a1),a1 ;calc end address
- ..loop move.l (a0)+,(a1)+ ;move it over
- cmpa.l a0,a2 ;finished?
- bpl.b ..loop ;nope! more yet
-
- move.l (kickmem,pc),d0 ;set up all the
- addi.l #524288,d0 ;pointers to each
- move.l d0,(table1) ;table1
- move.l #512,d1
- add.l d1,d0
- move.l d0,(table2) ;table2
- add.l d1,d0
- move.l d0,(table3) ;table3
- addi.l #16384,d0
- move.l d0,(table22) ;table2/2
- add.l d1,d0
- move.l d0,(table23) ;table2/3
- addi.l #16384,d0 ;last on is our struct
- movea.l d0,a4 ;save, need it later
- move.l d0,(fr_struct,a4) ;save it
- move.l (table23,pc),(fr_table5,a4) ;fill
- move.l (table22,pc),(fr_table4,a4) ;er
- move.l (table3,pc),(fr_table3,a4) ;up
- move.l (table2,pc),(fr_table2,a4) ;please
- move.l (table1,pc),(fr_table1,a4)
- move.l (kickmem,pc),(fr_kickmem,a4)
- move.l #'FAST',(fr_id,a4) ;our id
- movea.l (table3,pc),a1 ;third level
- move.l d3,d0
- moveq #11,d1
- lsr.l d1,d0
- lea (a1,d0.l),a1
- move.l #$f00000,d1
- sub.l d3,d1
- moveq #63,d0 ;512k to remap = 64
- ..dokickm sub.l d1,(a1)+ ;convert to same address
- dbf d0,..dokickm ;till done
-
- movea.l (table3,pc),a0 ;third level
- lea ($1f00,a0),a0 ;$f80000 mapping
- moveq #63,d0 ;64 to do
- move.l (kickmem,pc),d1 ;get new block
- or.l #$405,d1 ;or in types
- ..dotable33 move.l d1,(a0)+ ;and map it new area
- addi.l #$2000,d1 ;each is 8k
- dbf d0,..dotable33 ;till done
-
- movea.l (table1,pc),a0 ;get first table
- move.l (table2,pc),d0 ;get second table
- or.b #3,d0 ;UDT descriptor
- move.l d0,(a0)+ ;shove it in
- move.l (table22,pc),d0 ;get 2nd table 2
- or.b #3,d0 ;UDT descriptor
- move.l d0,(a0)+ ;shove it in
- move.l a4,(a0) ;link our struct on
- movea.l (table2,pc),a0 ;get table 2
- move.l (table3,pc),d2 ;get table 3
- moveq #127,d0 ;128 entries
- or.l #3,d2 ;UDT descriptor
- ..dotable2 move.l d2,(a0)+ ;move one in
- addi.l #128,d2 ;add next address
- dbf d0,..dotable2 ;loop till done
-
- CALLEXEC Disable ;implies Forbid
- movea.l (table1,pc),a2 ;get table start
- move.l a2,(urpreg) ;load print var
- move.l a2,(srpreg) ;load print var
- move.l #inson,(insstr) ;load print var
- move.l #daton,(datstr) ;load print var
- cmpi.l #$80008000,(dcaches,pc) ;all caches on?
- beq.b .callon ;skip if so
- move.l #datoff,(datstr) ;else change print var
- .callon lea (chipfast,pc),a0 ;tell we're changing it
- Printf
- lea (changemmu,pc),a5 ;get main code
- CALLEXEC Supervisor ;go do it
- JSREXEC Enable ;turn it all back on
- move.l #MEMF_PUBLIC,d1
- moveq #12,d0
- JSREXEC AllocMem
- tst.l d0
- beq.b .skpname
- movea.l d0,a1
- lea (memname,pc),a0
- ..copname move.b (a0)+,(a1)+
- bne.b ..copname
- movea.l d0,a1
- .skpname JSREXEC Forbid
- movea.l d3,a0 ;set base address
- move.l d3,d1 ;make a copy
- andi.l #$fffff,d1 ;clear any leading 1
- move.l #$100000,d0 ;a meg boundary
- sub.l d1,d0 ;less d1 = size to bound
- move.l #MEMF_CHIP|MEMF_PUBLIC|MEMF_LOCAL|MEMF_24BITDMA,d1 ;its chip
- moveq #-10,d2 ;chip priority -10
- pushregs ;save regs
- movea.l (4).w,a6 ;get exec
- movea.l (MemList,a6),a2 ;get the memlist
- .doloop cmp.l (MH_UPPER,a2),d3 ;get the upper bound
- bne.b .incit ;if not ours then inc
- cmp.w (MH_ATTRIBUTES,a2),d1 ;are the atts equal
- bne.b .doadd ;addmemlist if not
- add.l d0,d3 ;calc upper
- move.l d3,(MH_UPPER,a2) ;change upper bound
- movea.l (MH_FIRST,a2),a3 ;get the MC struct
- ..loop1 tst.l (MC_NEXT,a3) ;last one?
- beq.b .gotlast ;yep branch
- movea.l (MC_NEXT,a3),a3 ;get next
- bra.b ..loop1 ;and loop
- .gotlast add.l d0,(MC_BYTES,a3) ;add mem to chunk
- add.l d0,(MH_FREE,a2) ;and to total
- bra.b .finadd ;and exit
- .incit movea.l (LN_SUCC,a2),a2 ;get next
- tst.l (a2) ;last ?
- bne.b .doloop ;nope! loop
- bra.b .finadd ;yep! finish
- .doadd JSREXEC Permit
- popregs
- JSREXEC AddMemList ;add the memory
- bra.b .xitadd
- .finadd JSREXEC Permit
- popregs
- .xitadd lea (fastinst,pc),a0 ;get all done string
- bra.w printit ;and exit
-
- ;*************************************
- ;At this point the chiprom OS is alive
- ;and we are going to change it over to
- ;the fastrom setup. We flush all atc
- ;entries and all caches, so that any
- ;references to the chip OS are gone.
- ;************************************
-
- changemmu moveq #0,d0 ;set for caches off
- movec d0,cacr ;turn the caches off
- movec d0,tc ;turn MMU off
- nop
- pflusha ;invalidate all ATC
- cpusha bc ;flush all caches
- cinva bc ;inavalidate all
- nop
- movec dtt0,d0 ;get dtt0
- move.l d0,(dt0) ;set print var
- movec dtt1,d0 ;get dtt1
- move.l d0,(dt1) ;set print var
- movec itt0,d0 ;get itt0
- move.l d0,(it0) ;set print var
- movec itt1,d0 ;get itt1
- move.l d0,(it1) ;set print var
- movec vbr,d0 ;get vbr
- move.l d0,(vbreg) ;set print var
- movec a2,urp ;set new urp
- movec a2,srp ;and srp
- move.l #$c000,d0 ;mmu on 8k pages
- move.w d0,(tcreg) ;set print var
- movec d0,tc ;MMU on
- move.l (dcaches,pc),d0 ;cache settings
- movec d0,cacr ;set caches
- rte ;finished
-
- ;**********************************************
- ;This is the trapcode handler to check if we
- ;have a 68040 in the system. The instruction
- ;used before always gave an exception and will
- ;come here. We get the supplied exception from
- ;the stack and we check if it is a privilege
- ;violation, if so we have a 68040 and we return
- ;the URP in D0, and TC in D1, else we return
- ;NULL in D0.
- ;**********************************************
-
- test040 move.l (sp)+,d0 ;get Amiga exception
- cmpi.w #8,d0 ;privilege violation?
- bne.b .not040 ;skip if not
- movec urp,d0 ;get the urp reg
- movec tc,d1
- .trapxit addq.l #4,(2,sp) ;skip movec instruction
- rte ;return from exeption
- .not040 moveq #0,d0 ;clear return reg
- bra.b .trapxit ;and exit
-
- ;**********************************************
- ;This routine will manipulate a register on the
- ;PP&S 68040 card so that the next boot will
- ;switch to the required processor. The choice
- ;to switch or abort is done via the V2.04
- ;function, EasyRequestArgs.
- ;**********************************************
-
- doswitch lea ($800c000),a2 ;address of PP&S register
- move.l #68040,(from) ;set data for RDF string
- move.l #68030,(to) ;set data for RDF string
- move.b (a2),d0 ;get a byte
- not.b d0 ;invert it
- beq.b .mode030 ;if zero we're in 68040
- move.l #68030,(from) ;set data for RDF string
- move.l #68040,(to) ;set data for RDF string
- .mode030 move.l d0,d2 ;save current mode
- move.l #from,d0 ;get data for RDF string
- clr.l (esidcmp)
- bsr.b requester ;do the EasyRequestArgs
- tst.l d0 ;which gadget?
- beq.b .dsexit ;abort
- tst.b d2
- beq.b .do030
- move.l #-1,(a2) ;set for 68040
- move.l #-1,(a2) ;push it twice
- cmpi.b #-1,(a2) ;read it byte! did it set?
- beq.b .pok ;PP&S is here!
- .pperr bra.w perr ;else they dunna got one
- .do030 move.l (a2),d2 ;save current mode
- move.l #$fefefefe,(a2) ;set for 68030
- move.l #$fefefefe,(a2) ;set long
- cmpi.b #$fe,(a2) ;check read byte
- bne.b .pperr ;if not no PP&S here!
- .pok lea (easyreq,pc),a0 ;else get easy struct
- move.l #esabort,(es_GadgetFormat,a0) ;change the gadgets
- move.l #esboot,(es_TextFormat,a0) ;and the the text
- moveq #0,d0 ;no data
- move.l d0,(esidcmp)
- bsr.b requester ;will not come back
- ;unless they aborted
- move.l d2,($800c000) ;set old value back
- bsr.w flushcaches ;flush em
- .dsexit lea (credstr,pc),a0
- bsr.b .prntf
- lea (opabo,pc),a0 ;get aborted string
- .prntf Printf ;print it
- rts ;and we're gone..
-
-
- ;******************
- ;Call the requester
- ;******************
-
- requester movem.l a2-a3,-(sp) ;save non scratch
- suba.l a0,a0 ;WB window
- lea (easyreq,pc),a1 ;easy struct
- lea (esidcmp,pc),a2 ;null ext idcmp
- movea.l d0,a3 ;data for string
- CALLINT EasyRequestArgs ;do requester
- movem.l (sp)+,a2-a3 ;pop 'em
- rts ;and return
-
- ;********************************
- ;Data section
- ;Don't change the order of any
- ;vars, some print routines expect
- ;them in this order.
- ;********************************
-
- include "/set040/set040.i" ;structure definitions
-
- ioreq dc.l 0
- kickchip dc.l 0
- kickname dc.l 0
- from dc.l 0
- to dc.l 0
- _stdout dc.l 0
- kickmem dc.l 0
- table1 dc.l 0
- table2 dc.l 0
- table3 dc.l 0
- it0 dc.l 0
- it1 dc.l 0
- dt0 dc.l 0
- dt1 dc.l 0
- urpreg dc.l 0
- srpreg dc.l 0
- vbreg dc.l 0
- tcreg dc.w 0
- table22 dc.l 0
- table23 dc.l 0
- zcache dc.b 0
- mbspace dc.b 0
- scrtit dc.b 0
- noclick dc.b 0
- kickflag dc.b 0
- kludge dc.b 0
- datstr dc.l daton
- insstr dc.l inson
- dcaches dc.w $8000
- icaches dc.w $8000
- z3var1 dc.l $4fbc020
- z3var0 dc.l $8f7c020
- ver dc.b '$VER: Set040 1.14 (15.3.92)',0
- tdname dc.b 'trackdisk.device',0
- credstr dc.b $0a,$1b,'[1;33m',$1b,'[4mSet040 V1.14 ',$1b,'[31m',$1b,'[4mWritten in Assembler by Nic Wilson',$1b,'[0m',$0a,$0a,0
- infostr dc.b 'Level A ->',$1b,'[0;32m$%lx ',$1b,'[0mLevel B ->',$1b,'[0;32m$%lx',$1b,'[0m Level C ->',$1b,'[0;32m$%lx',$0a,$0a
- dc.b $1b,'[0mITT0 ->',$1b,'[32m$%-8.lx',$1b,'[0m ITT1 ->',$1b,'[32m$%-8.lx ',$1b,'[0m',$0a
- dc.b 'DTT0 ->',$1b,'[32m$%-8.lx',$1b,'[0m DTT1 ->',$1b,'[32m$%-8.lx',$1b,'[0m',$0a
- dc.b 'URP ->',$1b,'[32m$%-8.lx',$1b,'[0m SRP ->',$1b,'[32m$%-8.lx',$1b,'[0m',$0a
- dc.b 'VBR ->',$1b,'[32m$%-8.lx',$1b,'[0m TC ->',$1b,'[32m$%-4.x',$1b,'[0m',$0a,0
- usage dc.b $0a,'USAGE-> ',$1b,'[0;33mSet040 <switch> (only one ',"'-'",' switch is permitted).',$0a
- dc.b $1b,'[0;33m',TAB,'If no switch is supplied, the current setup will be displayed,',$0a
- dc.b TAB,'and if a CHIPROM setup is found, it will be changed to FASTROM ',$1b,'[0m',$0a
- dc.b $1b,'[0;32m-f<args> = install FASTROM with optional parameters (EG. -fzi).',$1b,'[0m',$0a
- dc.b $1b,'[0;33m',TAB,'If no arguments are supplied, a default FASTROM will be installed.',$1b,'[0m',$0a
- dc.b TAB,'z = allow caching of ZorroII memory space ($200000 - $A00000).',$0a
- dc.b TAB,'w = set ($1000000 - $3FFFFFF) as Writethrough.',$0a
- dc.b TAB,'c = set ($4000000 - $FFFFFFF) as Writethrough.',$0a
- dc.b TAB,'d = do not enable data cache.',$0a
- dc.b TAB,'i = do not enable instruction cache.',$0a
- dc.b TAB,'t = do not change Workbench screen title.',$0a
- dc.b TAB,'n = patch to stop floppy drives clicking.',$0a
- dc.b $1b,'[0;32m-k <file> = Load, install and boot a different kickstart',$1b,'[0m',$0a
- dc.b ' <file> = Path and filename to kickstart file (1.2 - 2.0).',$0a
- dc.b TAB,' For loading from Kickstart or SuperKickstart disk,',$0a
- dc.b TAB,' use floppy drive name for <file> (EG. Set040 -k DF0:).',$0a
- dc.b $1b,'[0;32m-c<args> = manipulate caches as per options (EG. -cIdC).',$1b,'[0m',$0a
- dc.b TAB,'I = Enable Instruction Cache.',$0a
- dc.b TAB,'i = Disable Instruction Cache.',$0a
- dc.b TAB,'D = Enable Data Cache.',$0a
- dc.b TAB,'d = Disable Data Cache.',$0a
- dc.b TAB,'B = Enable Both Caches.',$0a
- dc.b TAB,'b = Disable Both Caches.',$0a
- dc.b TAB,'A = Enable Both Caches & Copyback ($4000000 - $FFFFFFF).',$0a
- dc.b TAB,'a = Disable Both Caches & Copyback ($4000000 - $FFFFFFF).',$0a
- dc.b TAB,'C = Enable Copyback ($4000000 - $FFFFFFF).',$0a
- dc.b TAB,'c = Disable Copyback ($4000000 - $FFFFFFF).',$0a
- dc.b $1b,'[0;32m-r',TAB,' = remove FASTROM & reclaim resources.',$1b,'[0m',$0a
- dc.b $1b,'[0;32m-s',TAB,' = Switch CPU 68040-><-68030 (PP&S A3000 Card Only)',$1b,'[0m',$0a,0
- usage1 dc.b 'For usage, type -> ',$1b,'[32mSet040 ?',$1b,'[0m',$0a,0
- kickstr dc.b $1b,'[0mKickstart physical address ->',$1b,'[32m$%lx',$1b,'[0m',$0a,0
- daton dc.b 'DATA CACHE ENABLED ',0
- datoff dc.b 'DATA CACHE DISABLED ',0
- inson dc.b 'INST CACHE ENABLED ',$0a,$0a,0
- insoff dc.b 'INST CACHE DISABLED ',$0a,$0a,0
- fastinst dc.b 'FASTROM is installed. ',$0a,0
- kickinst dc.b 'KICKROM is installed. ',$0a,0
- remstr dc.b $0A,'FASTROM removed OK!',$0a,0
- error dc.b 'ERROR -> ',0
- unkmmu dc.b 'UNKNOWN MMU SETUP!!',$0a,0
- badkick dc.b 'CANNOT REMOVE A KICKROM SETUP!',$0a,0
- ourrom dc.b 'FASTROM already installed!',$0a,0
- norom dc.b 'FASTROM not installed!',$0a,0
- verstr dc.b 'AmigaDOS V2.04 (V37) or greater required.',$0a,0
- cpustr dc.b 'A 68040 CPU is not installed in this system.',$0a,0
- mmustr dc.b 'MMU already in use, I cannot install FASTROM/KICKROM.',$0a,0
- ppserr dc.b 'A PP&S A3000 card must be installed.',0
- baddrive dc.b 'Opening drive.',$0a,0
- readerr dc.b 'That disk was not a kickstart disk.',$0a,0
- notkickf dc.b 'File is not a kickstart file.',$0a,0
- memstr dc.b 'Could not get memory for '
- strkick dc.b 'KickStart.',$0a,0
- strtrans dc.b 'translation tables.',$0a,0
- strstruct dc.b 'structure.',$0a,0
- chipfast dc.b $0A,'Converting CHIPROM to FASTROM',$0a,0
- patch dc.b 'Patching Kickstart to stop MMU being disabled',0
- opabo dc.b 'Operation aborted.',$0a,0
- memname dc.b 'chip memory',0
-
- END
-
-