chiark / gitweb /
Create readable text `.bas' for each tokenized BASIC `,ffb' file.
[ssr] / StraySrc / Hammer / s / armEmul
1 ;
2 ; armEmul.s
3 ;
4 ; ARM emulation (MDW/TMA)
5 ;
6 ; © 1994-1998 Straylight
7 ;
8
9 ;----- Licensing note -------------------------------------------------------
10 ;
11 ; This file is part of Straylight's Sledgehammer debugger.
12 ;
13 ; Sledgehammer is free software; you can redistribute it and/or modify
14 ; it under the terms of the GNU General Public License as published by
15 ; the Free Software Foundation; either version 2, or (at your option)
16 ; any later version.
17 ;
18 ; Sledgehammer is distributed in the hope that it will be useful,
19 ; but WITHOUT ANY WARRANTY; without even the implied warranty of
20 ; MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
21 ; GNU General Public License for more details.
22 ;
23 ; You should have received a copy of the GNU General Public License
24 ; along with Sledgehammer.  If not, write to the Free Software Foundation,
25 ; 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
26
27 ;----- Don't forget these things --------------------------------------------
28 ;
29 ; SWP
30 ; Trans pin on LDR/STR
31
32 ;----- Standard header ------------------------------------------------------
33
34                 GET     libs:header
35                 GET     libs:swis
36
37                 GET     libs:stream
38
39 ;----- External dependencies ------------------------------------------------
40
41                 GET     sh.brkpt
42                 GET     sh.diss
43
44 ;----- Main code ------------------------------------------------------------
45
46                 AREA    |Hammer$$Code|,CODE,READONLY
47
48 ; --- ae_addr ---
49 ;
50 ; On entry:     --
51 ;
52 ; On exit:      R0 == address of armEmul routine
53 ;
54 ; Use:          Returns the address of the arm emulation code, for speedy
55 ;               calling.
56
57                 EXPORT  ae_addr
58 ae_addr         ADR     R0,armEmul
59                 MOVS    PC,R14
60
61 ; --- armEmul ---
62 ;
63 ; On entry:     R0 == pointer to register block
64 ;
65 ; On exit:      Flags corrupted
66 ;               May return error
67 ;
68 ; Use:          Emulates a given ARM instruction.
69
70                 EXPORT  armEmul
71 armEmul         ROUT
72
73                 STMFD   R13!,{R0-R12,R14}       ;Save some registers
74                 MOV     R1,R0                   ;Keep the register block ptr
75                 LDR     R2,[R1,#15*4]           ;Load current PC value
76                 BIC     R0,R2,#&FC000003        ;Clear the PSR bits
77                 BL      ae__translateAddr       ;Translate the address
78                 LDR     R0,[R0,#0]              ;Load the instruction
79
80  ; --- Debugging stuff ---
81
82  [ {FALSE}
83  IMPORT stream_regDump
84  STMFD  R13!,{R0-R2}
85  SWI    Stream_WriteS
86  =      "armEmul entered with instruction:",13,10,0
87  BIC    R0,R2,#&FC000003
88  BL     diss_address
89  LDR    R0,[R13,#0]
90  BL     diss_disassemble
91  SWI    Stream_Write0
92  SWI    Stream_NewLine
93
94  MOV    R0,R1
95  BL     stream_regDump
96  LDMIA  R13!,{R0-R2}
97  RDUMP
98  ]
99
100                 ; --- Make sure we need to execute the instruction ---
101
102                 MOV     R3,R0,LSR #28           ;Get the condition bits
103                 ADR     R14,ae__condTbl         ;Point to the cunning table
104                 AND     R4,R3,#&E               ;Get rid of the bottom bit
105                 LDR     R4,[R14,R4,LSL #1]      ;Load the entry we want
106                 MOV     R6,#&FF                 ;A vaguely useful value
107                 TST     R3,#1                   ;Is this a complement
108                 BEQ     %10armEmul              ;No -- handle it then
109
110                 ; --- We can work directly from the table ---
111
112                 ANDS    R14,R6,R4               ;Get the bottom byte
113                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
114                 CMP     R5,R14,LSR #4           ;Does it match?
115                 BEQ     %20armEmul              ;Yes -- we actually execute
116
117                 ANDS    R14,R6,R4,LSR #8        ;Get the next byte
118                 BEQ     ae__next                ;Nothing there -- advance PC
119                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
120                 CMP     R5,R14,LSR #4           ;Does it match?
121                 BEQ     %20armEmul              ;Yes -- we actually execute
122
123                 ANDS    R14,R6,R4,LSR #16       ;Get the next byte
124                 BEQ     ae__next                ;Nothing there -- advance PC
125                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
126                 CMP     R5,R14,LSR #4           ;Does it match?
127                 BEQ     %20armEmul              ;Yes -- we actually execute
128
129                 B       ae__next                ;Nothing there -- advance PC
130
131                 ; --- Handle complementary conditions :-) ---
132
133 10armEmul       ANDS    R14,R6,R4               ;Get the bottom byte
134                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
135                 CMP     R5,R14,LSR #4           ;Does it match?
136                 BEQ     ae__next                ;Yes -- don't do it then
137
138                 ANDS    R14,R6,R4,LSR #8        ;Get the next byte
139                 BEQ     %20armEmul              ;Yes -- then execute it
140                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
141                 CMP     R5,R14,LSR #4           ;Does it match?
142                 BEQ     ae__next                ;Yes -- don't do it then
143
144                 ANDS    R14,R6,R4,LSR #16       ;Get the next byte
145                 BEQ     %20armEmul              ;Yes -- then execute it
146                 AND     R5,R14,R2,LSR #28       ;Get the bits we want
147                 CMP     R5,R14,LSR #4           ;Does it match?
148                 BEQ     ae__next                ;Yes -- don't do it then
149
150                 B       %20armEmul              ;Got all the way -- do it
151
152                 ; --- The condition table ---
153                 ;
154                 ; Format of each byte:
155                 ;
156                 ; Bits  Meaning
157                 ; 0-3   AND mask for processor flags
158                 ; 4-7   Value to match for condition true
159
160 ae__condTbl     DCD     &00000004               ;NE (!Z)
161                 DCD     &00000002               ;CC (!C)
162                 DCD     &00000008               ;PL (!N)
163                 DCD     &00000001               ;VC (!V)
164                 DCD     &00000244               ;LS (!C | Z)
165                 DCD     &00001989               ;LT (N & !V) | (!N & V)
166                 DCD     &00441989               ;LE (N&!V) | (!N&V) | Z
167                 DCD     &00000010               ;NV --
168
169                 ; --- Dispatch an instruction ---
170
171 20armEmul       AND     R14,R0,#&0C000000       ;Get the opcode field
172                 ADD     PC,PC,R14,LSR #24       ;Just dispatch on that then
173                 DCB     "TMA!"
174
175                 B       ae__type00
176                 B       ae__type01
177                 B       ae__type10
178                 B       ae__type11
179
180                 ; --- Normal return point ---
181
182 ae__next        AND     R3,R2,#&FC000003        ;Look after PSR bits
183                 ADD     R2,R2,#4                ;Bump PC on a bit
184                 BIC     R2,R2,#&FC000003        ;Kill off PSR bits
185                 ORR     R2,R2,R3                ;Bolt on the old PSR
186
187 ae__return      LDR     R3,[R1,#15*4]           ;Get the old PC
188                 AND     R3,R3,#&3               ;Get just the mode flags
189                 AND     R4,R2,#&3               ;Get the new mode flags
190                 CMP     R4,R3                   ;Has the mode changed?
191                 BEQ     %90armEmul              ;No -- jump ahead
192
193                 ; --- The processor mode has changed ---
194
195                 CMP     R4,#2                   ;Are we now in IRQ?
196                 CMPNE   R4,#1                   ;Or FIQ?
197                 ADREQ   R0,ae__invMode          ;Yes -- point to error
198                 LDMEQFD R13!,{R0-R12,R14}       ;...load registers back
199                 ORREQS  PC,R14,#V_flag          ;...and return with error
200                 MOV     R6,R13                  ;Remember current R13 value
201                 ADD     R5,R1,#13*4             ;Point to saved R13
202                 LDMIA   R5,{R13,R14}            ;Load correct registers
203                 CMP     R4,#0                   ;Are we entering user mode?
204                 SWINE   XOS_EnterOS             ;No -- must be entering SVC
205                 TEQEQP  PC,#0                   ;Yes -- enter it then
206                 MOV     R0,R0                   ;A no-op -- keep ARM happy
207                 STMIA   R5,{R13,R14}            ;Store new register values
208                 MOV     R13,R6                  ;Restore my stack pointer
209                 LDR     R14,[R13,#13*4]         ;Load the link register
210                 BIC     R14,R14,#3              ;Clear the current mode
211                 ORR     R14,R14,R4              ;Enter the new mode
212                 STR     R14,[R13,#13*4]         ;Store back modified R14
213
214                 ; --- Return as normal ---
215
216 90              STR     R2,[R1,#15*4]           ;Save the new PC back
217                 LDMFD   R13!,{R0-R12,R14}       ;Get registers back
218                 BICS    PC,R14,#V_flag          ;Return without error
219
220                 LTORG
221
222 ae__invMode     DCD     1
223                 DCB     "Sledgehammer can only operate in "
224                 DCB     "User or Supervisor mode",0
225
226 ; --- ae__type00 ---
227 ;
228 ; On entry:     R0 == instruction to execute
229 ;               R1 == pointer to register block
230 ;
231 ; On exit:      R3-R12 mangled beyond redemption
232 ;
233 ; Use:          Emulates a type 0 ARM instruction.
234
235 ae__type00      ROUT
236
237                 AND     R3,R0,#&0FC00000        ;Get the op code
238                 AND     R4,R0,#&000000F0        ;We need these bits too
239
240                 ; --- See if it is a multiply instruction ---
241
242                 CMP     R3,#0                   ;Multiply instruction?
243                 CMPEQ   R4,#&90                 ;Double check
244                 BEQ     ae__multiply            ;Yes -- deal with it then
245
246                 ; --- Is it a SWP instruction ---
247
248                 CMP     R3,#&01000000           ;Is this bit set?
249                 CMPNE   R3,#&01400000           ;Or maybe this bit too?
250                 CMPEQ   R4,#&90                 ;Double check
251                 BEQ     ae__swp                 ;Yes -- deal with it
252
253                 ; --- Is it an undefined operation? ---
254
255                 AND     R3,R3,#&03000000        ;Get the correct bits
256                 AND     R4,R4,#&00000090        ;Are these bits set too?
257                 CMP     R3,#&01000000           ;Is opcode 0001?
258                 CMPEQ   R4,#&00000090           ;And are these bits set?
259                 BNE     ae__aluOp               ;No -- deal with alu Op then
260
261                 DCD     &E6000090               ;It's undefined, you know
262
263                 LTORG
264
265 ; --- ae__type01 ---
266 ;
267 ; On entry:     R0 == instruction to execute
268 ;               R1 == pointer to register block
269 ;
270 ; On exit:      R3-R12 mangled beyond redemption
271 ;
272 ; Use:          Emulates a type 1 ARM instruction.
273
274 ae__type01      ROUT
275
276                 ; --- See if it's undefined ---
277
278                 TST     R0,#(1<<25)             ;Is bit 25 set?
279                 TSTNE   R0,#(1<<4)              ;And bit 4?
280                 BEQ     ae__sDataTrans          ;No -- data transfer then
281
282                 DCD     &E6000090               ;It's undefined, you know
283
284                 LTORG
285
286 ; --- ae__type10 ---
287 ;
288 ; On entry:     R0 == instruction to execute
289 ;               R1 == pointer to register block
290 ;
291 ; On exit:      R3-R12 mangled beyond redemption
292 ;
293 ; Use:          Emulates a type 2 ARM instruction.
294
295 ae__type10      ROUT
296
297                 TST     R0,#(1<<25)             ;Is this bit set?
298                 BNE     ae__branch              ;Yes -- it's a branch
299                 B       ae__mTransfer           ;Must be LDM/STM then
300
301                 LTORG
302
303 ; --- ae__type11 ---
304 ;
305 ; On entry:     R0 == instruction to execute
306 ;               R1 == pointer to register block
307 ;
308 ; On exit:      R3-R12 mangled beyond redemption
309 ;
310 ; Use:          Emulates a type 3 ARM instruction.
311
312 ae__type11      ROUT
313
314                 TST     R0,#(1<<25)             ;Is this bit clear?
315                 BEQ     ae__coDataTran          ;Yes -- do co proc data trans
316
317                 AND     R8,R0,#&0F000000        ;Get top nibble of opcode
318                 CMP     R8,#&0F000000           ;Is it a SWI instruction?
319                 BEQ     ae__swi                 ;Yes -- deal with it
320
321                 TST     R0,#(1<<4)              ;Is it a coregister transfer?
322                 BNE     ae__coRegTran           ;Yes -- deal with it
323
324                 B       ae__coDataOp            ;Do a co-proc data op
325
326                 LTORG
327
328 ; --- ae__multiply ---
329 ;
330 ; On entry:     R0 == instruction to do
331 ;               R1 == pointer to register block
332 ;               R2 == current PC value
333 ;
334 ; On exit:      R2 updated
335 ;               R3-R12 trashed totally
336 ;
337 ; Use:          Emulates a MUL/MLA instruction
338
339 ae__multiply    ROUT
340
341                 MOV     R3,#&F                  ;A useful value
342                 AND     R8,R0,R3                ;Get Rm
343                 AND     R5,R3,R0,LSR #8         ;Get Rs
344                 AND     R6,R3,R0,LSR #12        ;Get Rn too
345                 AND     R7,R3,R0,LSR #16        ;Finally, get Rd
346
347                 CMP     R8,#15                  ;Is Rm really the PC?
348                 LDR     R4,[R1,R8,LSL #2]       ;Load my values
349                 ADDEQ   R4,R4,#12               ;Yes -- bump it along
350
351                 CMP     R5,#15                  ;Is Rs really the PC?
352                 LDR     R5,[R1,R5,LSL #2]
353                 ADDEQ   R5,R5,#8                ;Yes -- bump it up
354                 BICEQ   R5,R5,#&FC000003        ;And clear the PSR flags (!)
355
356                 CMP     R6,#15                  ;Is Rn really the PC?
357                 LDR     R6,[R1,R6,LSL #2]       ;Yes -- load accumulate
358                 ADDEQ   R6,R6,#8                ;Yes -- bump it up
359
360                 CMP     R7,R8                   ;Is Rd == Rm?
361                 BEQ     %10ae__multiply         ;Yes -- then handle weirdly
362
363                 TST     R0,#(1<<21)             ;Is it an MLA?
364                 MLANE   R8,R4,R5,R6             ;...and do the MLA
365                 MULEQ   R8,R4,R5                ;No -- Do the multiply
366                 B       %20ae__multiply         ;And set up the results
367
368                 ; --- Berk put Rd == Rm -- emulate faithfully ---
369
370 10ae__multiply  TST     R0,#(1<<21)             ;Is it an MLA?
371                 DCD     &10246594               ;MLANE  R4,R4,R5,R6
372                 DCD     &00040594               ;MULEQ  R4,R4,R5
373                 MOV     R8,R4                   ;And put result in nice reg
374
375                 ; --- Now write the results back ---
376
377 20ae__multiply  CMP     R7,#15                  ;Is destination the PC?
378                 STRNE   R8,[R1,R7,LSL #2]       ;No -- then store the result
379                 BIC     R2,R2,#Z_flag + N_flag  ;Clear the flags we modify
380                 CMP     R8,#0                   ;Is the result zero?
381                 ORREQ   R2,R2,#Z_flag           ;Yes -- set the Z bit
382                 ORRMI   R2,R2,#N_flag           ;Yes -- set the N bit
383                 B       ae__next                ;And get the next instruction
384
385                 LTORG
386
387 ; --- ae__branch ---
388 ;
389 ; On entry:     R0 == instruction to do
390 ;               R1 == pointer to register block
391 ;               R2 == current PC value
392 ;
393 ; On exit:      R3-R12 trashed totally
394 ;
395 ; Use:          Emulates a branch instruction
396
397 ae__branch      ROUT
398
399                 ; --- First try to do the link business ---
400
401                 TST     R0,#(1<<24)             ;Is the L bit set?
402                 ADDNE   R3,R2,#4                ;Bump on PC thing (overflow!)
403                 STRNE   R3,[R1,#14*4]           ;Save it in the reg block
404
405                 ; --- Now branch ---
406
407                 BIC     R3,R0,#&FF000000        ;Clear unwanted bits
408                 AND     R4,R2,#&FC000003        ;Look after PSR bits
409                 ADD     R2,R2,R3,LSL #2         ;Bump PC on a bit
410                 ADD     R2,R2,#8                ;And allow for `pipeline'
411                 BIC     R2,R2,#&FC000003        ;Kill off PSR bits
412                 ORR     R2,R2,R4                ;Bolt on the old PSR
413                 B       ae__return              ;And that's it for branch
414
415                 LTORG
416
417 ; --- ae__aluOp ---
418 ;
419 ; On entry:     R0 == instruction to do
420 ;               R1 == pointer to register block
421 ;               R2 == current PC value
422 ;
423 ; On exit:      R2 updated
424 ;               R3-R12 trashed totally
425 ;
426 ; Use:          Emulates a general ALU op instruction
427
428 ae__aluOp       ROUT
429
430                 ; --- Start building the instruction ---
431
432                 AND     R3,R0,#&03F00000        ;Get out:
433                                                 ;Immediate flag
434                                                 ;Opcode number
435                                                 ;S bit (FWIW)
436                 ORR     R3,R3,#&E0000000        ;Always execute this instr
437                 MOV     R11,#0                  ;Some interesting flags
438
439                 ; --- Work out the correct PC bump amount ---
440
441                 MOV     R12,#8                  ;By default it's 8
442                 TST     R0,#(1<<4)              ;Is the reg-shift bit on?
443                 MOVNE   R12,#12                 ;Yes -- then actually it's 12
444                 TST     R0,#(1<<25)             ;Unless the op's immediate
445                 MOVNE   R12,#8                  ;When it's actually 8 anyway
446
447                 ; --- Load the register values out ---
448
449                 MOV     R14,#&F                 ;Get a register mask
450
451                 AND     R4,R14,R0,LSR #12       ;Get Rd's number
452                 AND     R10,R0,#&01800000       ;Get the top two opcode bis
453                 CMP     R10,#&01000000          ;Is it a comparison instr?
454                 ORRNE   R3,R3,#8<<12            ;No -- put in fake Rd value
455                 BNE     %05ae__aluOp            ;And branch Ahead
456                 ORR     R11,R11,#1              ;Yes -- then remember this
457                 CMP     R4,#15                  ;Is a TEQP or the like?
458                 BNE     %05ae__aluOp            ;No -- branch ahead
459                 ORR     R3,R3,#8<<12            ;Put in fake Rd value
460                 BIC     R3,R3,#&01800000        ;Yes -- make a real ALU op
461                 ORR     R11,R11,#2              ;Remember we did this
462                 AND     R10,R0,#&00600000       ;Get the bottom two bits
463                 CMP     R10,#&00600000          ;Is it now an RSB?
464                 EOREQ   R3,R3,#&00E00000        ;Yes -- make it an ADD
465
466 05ae__aluOp     AND     R5,R14,R0,LSR #16       ;Get Rn's number too
467                 CMP     R5,#15                  ;Is Rn the PC?
468                 LDR     R5,[R1,R5,LSL #2]       ;Load the register value
469                 ADDEQ   R5,R5,R12               ;Yes -- then bump the value
470                 BICEQ   R5,R5,#&FC000003        ;And clear the PSR bits
471                 ORR     R3,R3,#5<<16            ;Put in our fake Rd value
472
473                 ; --- Now deal with Op2 ---
474
475                 TST     R0,#(1<<25)             ;Is the operand immediate?
476                 ORRNE   R8,R14,#&FF0            ;Build the number &FFF
477                 ANDNE   R8,R0,R8                ;Get bottom three nibbles
478                 ORRNE   R3,R3,R8                ;And bung 'em in my fake
479                 BNE     %10ae__aluOp            ;Yes -- deal with that then
480
481                 ; --- Handle Op2 registers ---
482
483                 AND     R6,R14,R0               ;Get Rm's number out
484                 CMP     R6,#15                  ;Is Rm the PC?
485                 LDR     R6,[R1,R6,LSL #2]       ;Load the register value
486                 ADDEQ   R6,R6,R12               ;Yes -- then bump the value
487                 ORR     R3,R3,#6<<0             ;Put our fake Rm value in
488
489                 ; --- Is the shift immediate or reg-done? ---
490
491                 TST     R0,#(1<<4)              ;Check the reg-shift bit
492                 ANDEQ   R7,R0,#&FF0             ;No -- get the gubbins out
493                 ORREQ   R3,R3,R7                ;And put it in our fake instr
494                 BEQ     %10ae__aluOp            ;And skip register mangling
495
496                 AND     R7,R14,R0,LSR #8        ;Get Rs's number out
497                 CMP     R7,#15                  ;Is Rs the PC?
498                 LDR     R7,[R1,R7,LSL #2]       ;Load the register value
499                 ADDEQ   R7,R7,#8                ;Rs always bumped by 8
500                 BICEQ   R7,R7,#&FC000003        ;And PSR bits are stripped
501                 ORR     R3,R3,#7<<8             ;Put that in there nicely
502                 AND     R8,R0,#&0F0             ;Get the shift type out
503                 ORR     R3,R3,R8                ;And put it in our fake instr
504
505                 ; --- Do the instruction ---
506
507 10ae__aluOp     LDR     R14,ae__retInstr        ;Get the return instruction
508                 STMFD   R13!,{R3,R14}           ;Save them on the stack
509
510                 MOV     R14,PC                  ;Get my current status
511                 AND     R14,R14,#&0C000003      ;Get the special flags
512                 AND     R10,R2,#&F0000000       ;Get all of his flags
513                 ORR     R10,R10,R14             ;Mix them with my status
514
515                 MOV     R14,PC                  ;Set up the return address
516                 ORRS    PC,R13,R10              ;And call the instruction
517                 ADD     R13,R13,#8              ;Restore the stack
518                 MOV     R12,PC                  ;Look after processor status
519
520                 ; --- Now stash the result away ---
521
522                 TST     R11,#1                  ;Was it a compare instr?
523                 TSTNE   R11,#2                  ;Is Rd the program counter?
524                 BNE     %50ae__aluOp            ;Yes -- P type comparison
525
526                 CMP     R4,#15                  ;Was destination the PC?
527                 BEQ     %40ae__aluOp            ;Yes -- this is special then
528
529                 TST     R11,#1                  ;Was it a compare instr?
530                 STREQ   R8,[R1,R4,LSL#2]        ;Store the result away
531                 TST     R0,#(1<<20)             ;Is the `S' bit set?
532                 ANDNE   R12,R12,#&F0000000      ;Get the status flags
533                 BICNE   R2,R2,#&F0000000        ;Clear the current ones
534                 ORRNE   R2,R2,R12               ;Set the flag appropriately
535                 B       ae__next                ;And branch to next instr
536
537                 ; --- The destination was PC ---
538
539 40ae__aluOp     EOR     R14,R2,R8               ;Get bits that WILL change
540                 TST     R0,#(1<<20)             ;Is the `S' bit set?
541                 BICEQ   R14,R14,#&FC000003      ;No -- don't update PSR
542                 TST     R2,#3                   ;Are we in user mode?
543                 BICEQ   R14,R14,#&0C000003      ;Yes -- update top 4 bits
544                 EOR     R2,R2,R14               ;Munge bits we really want
545                 B       ae__return              ;Return happily!@?
546
547                 ; --- There was a `P' suffix thingy ---
548
549 50ae__aluOp     EOR     R14,R2,R8               ;Get bits that WILL change
550                 AND     R14,R14,#&FC000003      ;Clear the PC bits
551                 TST     R2,#3                   ;Are we in user mode?
552                 BICEQ   R14,R14,#&0C000003      ;Yes -- update top 4 bits
553                 EOR     R2,R2,R14               ;Munge bits we really want
554                 B       ae__next                ;Return happily!@?
555
556 ae__retInstr    MOV     PC,R14                  ;Return, leave status alone
557
558                 LTORG
559
560 ; --- ae__swp ---
561 ;
562 ; On entry:     R0 == instruction to do
563 ;               R1 == pointer to register block
564 ;               R2 == current PC value
565 ;
566 ; On exit:      R2 updated
567 ;               R3-R12 trashed totally
568 ;
569 ; Use:          Emulates a SWP instruction
570
571 ae__swp         ROUT
572
573                 B       ae__next                ;Ignore it
574
575                 LTORG
576
577 ; --- ae__sDataTrans ---
578 ;
579 ; On entry:     R0 == instruction to do
580 ;               R1 == pointer to register block
581 ;               R2 == current PC value
582 ;
583 ; On exit:      R2 updated
584 ;               R3-R12 trashed totally
585 ;
586 ; Use:          Emulates LDR/STR instructions
587
588 ae__sDataTrans  ROUT
589
590                 ; --- Load the register values out ---
591
592                 MOV     R14,#&F                 ;Get a register mask
593                 MOV     R11,#0                  ;Some flags and things
594
595                 AND     R4,R14,R0,LSR #12       ;Get Rd's number
596                 AND     R5,R14,R0,LSR #16       ;Get Rn's number too
597                 CMP     R5,#15                  ;Is Rn the PC?
598                 LDR     R6,[R1,R5,LSL #2]       ;Load the register value
599                 ADDEQ   R6,R6,#8                ;Yes -- then bump the value
600                 BICEQ   R6,R6,#&FC000003        ;And clear the PSR bits
601                 CMP     R4,R5                   ;Is Rd==Rn?
602                 ORREQ   R11,R11,#4              ;Yes -- remember this
603
604                 ; --- Now deal with Op2 ---
605
606                 TST     R0,#(1<<25)             ;Is the operand immediate?
607                 ORREQ   R8,R14,#&FF0            ;Build the number &FFF
608                 ANDEQ   R8,R0,R8                ;Get bottom three nibbles
609                 BEQ     %10ae__sDataTrans       ;And skip register mangling
610
611                 AND     R7,R14,R0               ;Get the offset register
612                 CMP     R7,#15                  ;Is it the PC?
613                 LDR     R7,[R1,R7,LSL #2]       ;Load the register value
614                 ADDEQ   R7,R7,#8                ;Yes -- then bump the value
615
616                 AND     R8,R0,#&FF0             ;Get the constant shift bit
617                 ORR     R8,R8,#&E1000000        ;Do the shift by...
618                 ORR     R8,R8,#&00A00000        ;building MOV R8,R7,shift
619                 ORR     R8,R8,#&00008000
620                 ORR     R8,R8,#&00000007
621                 LDR     R14,ae__retInstr        ;Get the return instruction
622                 STMFD   R13!,{R8,R14}           ;Save them on the stack
623
624                 AND     R14,PC,#&0C000003       ;Get the special flags
625                 AND     R10,R2,#&F0000000       ;Get all of his flags
626                 ORR     R10,R10,R14             ;Mix them with my status
627
628                 MOV     R14,PC                  ;Set up the return address
629                 ORRS    PC,R13,R10              ;Execute the code nicely
630                 ADD     R13,R13,#8              ;Recover the stack I used
631
632                 ; --- R8 contains the offset -- get the address ---
633
634 10              MOV     R3,R0                   ;Preserve R0 for a bit
635                 TST     R3,#(1<<23)             ;Is the op an addition?
636                 RSBEQ   R8,R8,#0                ;No -- then make it negative
637                 TST     R3,#(1<<24)             ;Is the op pre-indexed?
638                 ADDNE   R7,R6,R8                ;Yes -- form the address
639                 MOVEQ   R7,R6                   ;Otherwise just use base
640
641                 BIC     R0,R7,#3                ;Word align the address
642                 AND     R7,R7,#3                ;Get the non-word-alignedness
643                 BL      ae__translateAddr       ;Translate the address
644                 ORR     R7,R7,R0                ;Get the translated address
645                 MOV     R0,R3                   ;Put instruction back in R0
646
647                 ; --- Now work out whether it's a load or store ---
648
649                 TST     R0,#(1<<20)             ;Is it a load then?
650                 BEQ     %20ae__sDataTrans       ;No -- then do a store
651
652                 TST     R0,#(1<<22)             ;Does he only want a byte?
653                 LDREQ   R7,[R7,#0]              ;No -- load a word value
654                 LDRNEB  R7,[R7,#0]              ;Yes -- load a byte value
655
656                 ; --- Stuff the loaded value into a `register' ---
657
658                 CMP     R4,#15                  ;Is destination the PC?
659                 ORREQ   R11,R11,#1              ;Yes -- say we've updated it
660                 BICEQ   R7,R7,#&FC000003        ;Clear the PSR bits
661                 ANDEQ   R2,R2,#&FC000003        ;Keep his PSR bits
662                 ORREQ   R2,R2,R7                ;And mix 'em together
663                 STRNE   R7,[R1,R4,LSL #2]       ;Otherwise store the value
664                 B       %50ae__sDataTrans       ;Tidy everything up nicely
665
666                 ; --- Handle a store operation ---
667
668 20              CMP     R4,#15                  ;Is the register the PC?
669                 LDR     R4,[R1,R4,LSL #2]       ;Load the correct value out
670                 ADDEQ   R4,R4,#12               ;Bump the value along a bit
671
672                 TST     R0,#(1<<22)             ;Does he only want a byte?
673                 STREQ   R4,[R7,#0]              ;No -- store the whole word
674                 STRNEB  R4,[R7,#0]              ;Yes -- just store the byte
675
676                 ; --- Finish off -- do writeback maybe ---
677
678 50              MVN     R14,R0                  ;Toggle all the bits
679                 TST     R14,#(1<<24)            ;Is the postindexed bit on?
680                 TSTEQ   R0,#(1<<21)             ;Or is the writeback bit on?
681                 BEQ     %60ae__sDataTrans       ;No writeback -- skip on
682                 TST     R11,#4                  ;Is Rd==Rn?
683                 BNE     %60ae__sDataTrans       ;Yes -- don't corrupt Rd
684
685                 ; --- Perform the writeback ---
686
687                 ADD     R7,R6,R8                ;Get the resulting address
688                 CMP     R5,#15                  ;Is Rn the program counter
689                 ORREQ   R11,R11,#1              ;Yes -- say we've updated it
690                 BICEQ   R7,R7,#&FC000003        ;Clear the PSR bits
691                 ANDEQ   R2,R2,#&FC000003        ;Keep his PSR bits
692                 ORREQ   R2,R2,R7                ;And mix 'em together
693                 STRNE   R7,[R1,R5,LSL #2]       ;Otherwise store the value
694
695                 ; --- Finally return to the main thing ---
696
697 60              TST     R11,#1                  ;Did we modify the PC?
698                 BNE     ae__return              ;Yes -- don't advance PC
699                 BEQ     ae__next                ;Otherwise get next instr
700
701                 LTORG
702
703                 GBLA    count
704
705 ; --- ae__mTransfer ---
706 ;
707 ; On entry:     R0 == instruction to do
708 ;               R1 == pointer to register block
709 ;               R2 == current PC value
710 ;
711 ; On exit:      R3-R12 trashed totally
712 ;
713 ; Use:          Emulates an LDM/STM instruction
714
715 ae__mTransfer   ROUT
716
717                 ; --- Load the register values out ---
718
719                 MOV     R14,#&F                 ;Get a register mask
720                 MOV     R11,#0                  ;Some flags and things
721
722                 AND     R4,R14,R0,LSR #16       ;Get Rn's number
723                 CMP     R4,#15                  ;Is Rn the PC?
724                 LDR     R5,[R1,R4,LSL #2]       ;Load the register value
725                 ADDEQ   R5,R5,#8                ;Yes -- then bump the value
726
727                 ; --- We need to know how may to transfer ---
728
729                 MOV     R7,#0                   ;The count so far
730 count           SETA    0
731                 WHILE   count<=15
732                 TST     R0,#1<<count
733                 ADDNE   R7,R7,#1
734 count           SETA    count+1
735                 WEND
736
737                 ; --- We need to know where we start writing from ---
738
739                 MOV     R14,R0                  ;Take a copy of the instr
740                 MOV     R6,R5                   ;The write-backed value
741                 TST     R0,#(1<<23)             ;Is this +ve increment?
742                 SUBEQ   R5,R5,R7,LSL #2         ;No -- subtract nicely
743                 SUBEQ   R6,R6,R7,LSL #2         ;...and apply writeback too
744                 MVNEQ   R14,R14                 ;...invert the copy
745                 ADDNE   R6,R6,R7,LSL #2         ;Otherwise add writeback
746                 TST     R14,#(1<<24)            ;Is it pre-indexed?
747                 ADDNE   R5,R5,#4                ;Yes -- then bump on one
748
749                 ; --- Pause for breath ---
750                 ;
751                 ; While we pant in our weary manner, we may as well examine
752                 ; the register allocation:
753                 ;
754                 ;  R1 == pointer to register block.  This is our only source
755                 ;        of register values to actually load or store.
756                 ;  R2 == the exception: this is the program counter
757                 ;  R3 == a bit which shifts along from pos 0 to 15
758                 ;  R4 == base register number
759                 ;  R5 == address to load/store next register
760                 ;  R6 == value to write back to base
761                 ;  R7 == pointer into register block
762                 ;  R8 == instruction  We will modify this by clearing `W'
763                 ;        once writeback is performed, to save time.
764                 ;  R11 == flags word
765                 ;
766                 ;  Just to confuse, R0 and R5 are about to be swapped.
767
768                 ; --- Initialise other register values ---
769
770                 MOV     R3,#1                   ;Start with R0
771                 MOV     R7,R1                   ;Point to R0's value
772                 MOV     R8,R0                   ;Put instruction in R8
773                 MOV     R11,#0                  ;No flags yet
774                 MVN     R14,R8                  ;Get inverted instruction
775                 TST     R2,#3                   ;Are we in !(user mode)?
776                 TSTNE   R8,#(1<<22)             ;...with 'S' set?
777                 TSTNE   R14,#(1<<15)            ;...and without PC in list?
778                 ORRNE   R11,R11,#2              ;Yes -- user mode transfer
779
780                 ; --- Now we wish to load/store each value ---
781
782 00ae__mTransfer TST     R8,R3                   ;Is the register required?
783                 BEQ     %40ae__mTransfer        ;No -- jump ahead
784
785                 MOV     R0,R5                   ;Put the address in R0
786                 BL      ae__translateAddr       ;Translate the address
787                 TST     R8,#(1<<20)             ;Are we loading?
788                 BEQ     %10ae__mTransfer        ;No -- do a store then
789
790                 TST     R3,#(1<<13)             ;Are we transferring R13?
791                 TSTEQ   R3,#(1<<14)             ;...or R14?
792                 TSTNE   R11,#2                  ;...with user mode transfer?
793                 BNE     %05ae__mTransfer        ;Yes -- special case
794
795                 LDR     R9,[R0],#4              ;Load a word
796                 CMP     R3,R10,LSL R4           ;Are we loading the base?
797                 BICEQ   R8,R8,#(1<<21)          ;Yes -- clear the 'W' flag
798                 TST     R3,#(1<<15)             ;Are we loading the PC?
799                 STREQ   R9,[R7,#0]              ;No -- store correctly away
800                 BEQ     %30ae__mTransfer        ;...and jump ahead
801
802                 ; --- We are loading into the PC ---
803
804                 EOR     R14,R2,R9               ;Get bits that WILL change
805                 TST     R8,#(1<<22)             ;Is the `S' bit set?
806                 BICEQ   R14,R14,#&FC000003      ;No -- don't update PSR
807                 TST     R2,#3                   ;Are we in user mode?
808                 BICEQ   R14,R14,#&0C000003      ;Yes -- update top 4 bits
809                 EOR     R2,R2,R14               ;Munge bits we really want
810                 ORR     R11,R11,#1              ;Say we changed PC
811                 B       %30ae__mTransfer        ;Tidy everything up nicely
812
813                 ; --- We are doing a user register transfer ---
814
815 05ae__mTransfer TST     R3,#(1<<13)             ;Transfering R13?
816                 LDMNEIA R5,{R13}^               ;Yes -- do that then
817                 LDMEQIA R5,{R14}^               ;No -- do R14 instead
818                 B       %30ae__mTransfer        ;Jump ahead
819
820                 ; --- Do a register store ---
821
822 10ae__mTransfer TST     R3,#(1<<14)+(1<<13)     ;Are we transferring R13/14?
823                 TSTNE   R2,#3                   ;...in a non-user mode?
824                 TSTNE   R8,#(1<<22)             ;...with 'S' set?
825                 BNE     %15ae__mTransfer        ;Yes -- special case
826
827                 TST     R3,#(1<<15)             ;Are we storing PC?
828                 LDREQ   R9,[R7,#0]              ;No -- load reg in question
829                 ADDNE   R9,R2,#12               ;Yes -- work out value
830                 STR     R9,[R0,#0]              ;Store it in memory
831                 B       %30ae__mTransfer        ;Jump ahead
832
833                 ; --- We are doing a user register transfer ---
834
835 15ae__mTransfer TST     R3,#(1<<13)             ;Transfering R13?
836                 STMNEIA R5,{R13}^               ;Yes -- do that then
837                 STMEQIA R5,{R14}^               ;No -- do R14 instead
838
839                 ; --- OK, get ready for the next one ---
840
841 30ae__mTransfer TST     R8,#(1<<21)             ;Is 'W' bit set?
842                 CMPNE   R4,#15                  ;Yes -- make sure it's not PC
843                 STRNE   R6,[R1,R4,LSL #2]       ;Yes -- do the writeback
844                 BICNE   R8,R8,#(1<<21)          ;...and clear the 'W' flag
845                 ADD     R5,R5,#4                ;Increment location addr
846
847 40ae__mTransfer ADD     R7,R7,#4                ;Point to the next register
848                 MOV     R3,R3,LSL #1            ;Move onto next register
849
850                 CMP     R3,#(1<<15)             ;Have we finished?
851                 BLE     %00ae__mTransfer        ;No -- keep on going then
852                 TST     R11,#1                  ;Did we modify PC?
853                 BEQ     ae__next                ;No -- go onto next
854                 BNE     ae__return              ;Yes -- just return
855
856                 LTORG
857
858 ; --- ae__coDataTran ---
859 ;
860 ; On entry:     R0 == instruction to do
861 ;               R1 == pointer to register block
862 ;               R2 == current PC value
863 ;
864 ; On exit:      R3-R12 trashed totally
865 ;
866 ; Use:          Emulates an LDC/STC instruction
867
868 ae__coDataTran  ROUT
869
870                 ; --- Load the register values out ---
871
872                 MOV     R14,#&F                 ;Get a register mask
873                 MOV     R11,#0                  ;Some flags and things
874
875                 AND     R5,R14,R0,LSR #16       ;Get Rn's number
876                 CMP     R5,#15                  ;Is Rn the PC?
877                 LDR     R6,[R1,R5,LSL #2]       ;Load the register value
878                 ADDEQ   R6,R6,#8                ;Yes -- then bump the value
879                 BICEQ   R6,R6,#&FC000003        ;And clear the PSR bits
880
881                 ; --- Now deal with Op2 ---
882
883                 AND     R8,R0,#&FF              ;Get bottom three nibbles
884                 MOV     R8,R8,LSL #2            ;Scale up properley
885                 MOV     R3,R0                   ;Preserve R0 for a bit
886                 TST     R3,#(1<<23)             ;Is the op an addition?
887                 RSBEQ   R8,R8,#0                ;No -- then make it negative
888                 TST     R3,#(1<<24)             ;Is the op pre-indexed?
889                 ADDNE   R7,R6,R8                ;Yes -- form the address
890                 MOVEQ   R7,R6                   ;Otherwise just use base
891                 ADD     R9,R6,R8                ;Remember this value
892
893                 BIC     R0,R7,#3                ;Word align the address
894                 AND     R7,R7,#3                ;Get the non-word-alignedness
895                 BL      ae__translateAddr       ;Translate the address
896                 ORR     R7,R7,R0                ;Get the translated address
897                 MOV     R0,R3                   ;Put instruction back in R0
898
899                 ; --- Now do the operation ---
900
901                 BIC     R8,R0,#&FF              ;Get the basic instruction
902                 BIC     R8,R8,#&01200000        ;Say its post indexed, no !
903                 BIC     R8,R8,#&000F0000        ;Clear the base register
904                 ORR     R8,R8,#(7<<16)          ;Use R7 instead
905
906                 LDR     R14,ae__retInstr        ;Get the return instruction
907                 STMFD   R13!,{R8,R14}           ;Save them on the stack
908
909                 AND     R14,PC,#&0C000003       ;Get the special flags
910                 AND     R10,R2,#&F0000000       ;Get all of his flags
911                 ORR     R10,R10,R14             ;Mix them with my status
912
913                 MOV     R14,PC                  ;Set up the return address
914                 ORRS    PC,R13,R10              ;Execute the code nicely
915                 ADD     R13,R13,#8              ;Recover the stack I used
916
917                 MVN     R14,R0                  ;Get inverted instruction
918                 TST     R14,#(1<<24)            ;Is the postindexed bit on?
919                 TSTEQ   R0,#(1<<21)             ;Or is the writeback bit on?
920                 BEQ     %60ae__coDataTran       ;No writeback -- skip on
921                 CMP     R5,#15                  ;Are we using R15 as base?
922                 STRNE   R9,[R1,R5,LSL #2]       ;No -- store updated
923
924                 ; --- Finally return to the main thing ---
925
926 60              B       ae__next                ;Get next instruction
927
928                 LTORG
929
930 ; --- ae__coRegTran ---
931 ;
932 ; On entry:     R0 == instruction to do
933 ;               R1 == pointer to register block
934 ;               R2 == current PC value
935 ;
936 ; On exit:      R3-R12 trashed totally
937 ;
938 ; Use:          Emulates an MCR/MRC instruction
939
940 ae__coRegTran   ROUT
941
942                 ; --- Load the register value out ---
943
944                 MOV     R14,#&F                 ;Get a register mask
945                 MOV     R11,#0                  ;Some flags and things
946
947                 AND     R5,R14,R0,LSR #12       ;Get Rn's number
948                 CMP     R5,#15                  ;Is Rn the PC?
949                 LDR     R6,[R1,R5,LSL #2]       ;Load the register value
950                 ADDEQ   R6,R6,#8                ;Yes -- then bump the value
951
952                 BIC     R8,R0,#&0000F000        ;Get the opcode without reg
953                 ORR     R8,R8,#(6<<12)          ;Use R6
954
955                 LDR     R14,ae__retInstr        ;Get the return instruction
956                 STMFD   R13!,{R8,R14}           ;Save them on the stack
957
958                 AND     R14,PC,#&0C000003       ;Get the special flags
959                 AND     R10,R2,#&F0000000       ;Get all of his flags
960                 ORR     R10,R10,R14             ;Mix them with my status
961
962                 MOV     R14,PC                  ;Set up the return address
963                 ORRS    PC,R13,R10              ;Execute the code nicely
964                 ADD     R13,R13,#8              ;Recover the stack I used
965
966                 TST     R0,#(1<<20)             ;Was it a load?
967                 BEQ     ae__next                ;No -- return then
968                 CMP     R5,#15                  ;Are we loading into the PC?
969                 STRNE   R6,[R1,R5,LSL #2]       ;No -- store value
970                 BNE     ae__next                ;...and return
971                 BIC     R2,R2,#&F               ;Clear status flags
972                 AND     R6,R6,#&F               ;Get the new ones
973                 ORR     R2,R2,R6                ;Put in the new ones
974                 BNE     ae__next                ;Return
975
976 ; --- ae__coDataOp ---
977 ;
978 ; On entry:     R0 == instruction to do
979 ;               R1 == pointer to register block
980 ;               R2 == current PC value
981 ;
982 ; On exit:      R3-R12 trashed totally
983 ;
984 ; Use:          Emulates a CDP instruction
985
986 ae__coDataOp    ROUT
987
988                 LDR     R14,ae__retInstr        ;Get the return instruction
989                 STMFD   R13!,{R0,R14}           ;Save them on the stack
990
991                 MOV     R14,PC                  ;Set up the return address
992                 MOV     PC,R13                  ;Execute the code nicely
993                 ADD     R13,R13,#8              ;Recover the stack I used
994
995                 B       ae__next                ;Go onto next instruction
996
997                 LTORG
998
999 ; --- ae__swi ---
1000 ;
1001 ; On entry:     R0 == instruction to execute
1002 ;               R1 == pointer to register block
1003 ;               R2 == program counter when it happened
1004 ;
1005 ; On exit:      R0-R2 preserved
1006 ;               R3-R12 mangled beyond recognition
1007 ;
1008 ; Use:          Emulates a SWI instruction.
1009
1010 ae__swi         ROUT
1011
1012                 ; --- Words of Wisdom ---
1013                 ;
1014                 ; There are problems with executing SWIs:
1015                 ;
1016                 ; User registers R0-R9 and R13 must be set up correctly.
1017                 ; User flags must be set up correctly too.
1018                 ;
1019                 ; This gives me exactly 4 registers to mess with.
1020
1021                 BIC     R3,R0,#&FF000000        ;Get the the SWI bits
1022                 BIC     R3,R3,#&00F20000        ;Clear off some other bits
1023
1024                 ; --- Check for some location-specific or odd SWIs ---
1025
1026                 CMP     R3,#OS_WriteS           ;Check for OS_WriteS
1027                 BEQ     %80ae__swi              ;Do this specially
1028                 CMP     R3,#OS_EnterOS          ;Check for OS_EnterOS
1029                 BEQ     %70ae__swi              ;Make it do a mode switch
1030                 LDR     R14,=Stream_WriteS      ;Also check for this
1031                 CMP     R3,R14                  ;Do they match nicely?
1032                 BEQ     %90ae__swi              ;And do this specially too
1033                 LDR     R14,=&CC180+9           ;Is it Sledge_Breakpoint?
1034                 CMP     R3,R14                  ;Quick check then
1035                 BEQ     ae__next                ;Yes -- ignore it totally
1036
1037                 ; --- Handle general SWIs ---
1038
1039                 STMFD   R13!,{R0-R2}            ;Save what I must preserve
1040
1041                 MOV     R4,PC                   ;Get my current status
1042                 AND     R3,R2,#&F0000000        ;Get the user's flags
1043                 AND     R4,R4,#&0C000003        ;And my special status
1044                 ORR     R3,R3,R4                ;Mix 'em together nicely
1045                 TEQP    R3,#0                   ;And set this as my status
1046
1047                 LDR     R14,ae__swiRet          ;Get the special return instr
1048                 STMFD   R13!,{R0,R14}           ;Save this on the stack
1049                 MOV     R12,R13                 ;Preserve stack ptr in R12
1050                 LDR     R13,[R1,#13*4]          ;Load user's stack pointer
1051                 LDMIA   R1,{R0-R9}              ;Load other SWI arguments
1052                 MOV     R11,PC                  ;Set up return address oddly
1053                 MOV     PC,R12                  ;Call the SWI instruction
1054
1055                 MOV     R10,PC                  ;Get the processor flags
1056                 ADD     R13,R12,#8              ;Restore the stack pointer
1057                 LDR     R12,[R13,#4]            ;Load the register block ptr
1058                 STMIA   R12,{R0-R9}             ;Stuff the SWI registers back
1059
1060                 LDMFD   R13!,{R0-R2}            ;Reload our important regs
1061                 AND     R14,R2,#3               ;Get the processor mode
1062                 CMP     R14,#SVC_mode           ;Are we in SVC mode?
1063                 ADDEQ   R14,R2,#4               ;Yes -- make a bogus value
1064                 STREQ   R14,[R1,#14*4]          ;And save over his R14 value
1065                 BIC     R2,R2,#&FC000003        ;Just get the PC bits
1066                 AND     R10,R10,#&FC000003      ;Get the returned PSR bits
1067                 ORR     R2,R2,R10               ;Mix 'em into the PC
1068                 B       ae__next                ;And carry on the good work
1069
1070                 ; --- Some special SWIs ---
1071
1072 80ae__swi       STMFD   R13!,{R0-R2}            ;Save what I must preserve
1073
1074                 MOV     R5,#&EF000000           ;Get the basic SWI opcode
1075                 ORR     R5,R5,#OS_Write0        ;Make it a particular SWI
1076                 TST     R0,#&00020000           ;Is the X bit set?
1077                 ORRNE   R5,R5,#&00020000        ;Yes -- set out one too
1078
1079                 MOV     R4,PC                   ;Get my current status
1080                 AND     R3,R2,#&F0000000        ;Get the user's flags
1081                 AND     R4,R4,#&0C000003        ;And my special status
1082                 ORR     R3,R3,R4                ;Mix 'em together nicely
1083                 TEQP    R3,#0                   ;And set this as my status
1084
1085                 LDR     R14,ae__swiRet          ;Get the special return instr
1086                 STMFD   R13!,{R5,R14}           ;Save this on the stack
1087                 MOV     R12,R13                 ;Preserve stack ptr in R12
1088                 LDR     R13,[R1,#13*4]          ;Load user's stack pointer
1089                 BIC     R0,R2,#&FC000003        ;Get the string address...
1090                 ADD     R0,R0,#4                ;... it's just after the SWI
1091                 MOV     R11,PC                  ;Set up return address oddly
1092                 MOV     PC,R12                  ;Call the SWI instruction
1093
1094                 MOV     R10,PC                  ;Get the processor flags
1095                 ADD     R13,R12,#8              ;Restore the stack pointer
1096                 MOV     R3,R0                   ;Get the string end pointer
1097
1098                 LDMFD   R13!,{R0-R2}            ;Reload our important regs
1099                 AND     R14,R2,#3               ;Get the processor mode
1100                 CMP     R14,#SVC_mode           ;Are we in SVC mode?
1101                 ADDEQ   R14,R2,#4               ;Yes -- make a bogus value
1102                 STREQ   R14,[R1,#14*4]          ;And save over his R14 value
1103
1104                 ADD     R3,R3,#3                ;Word align the string end
1105                 BIC     R3,R3,#3                ;To find the next instruction
1106                 AND     R10,R10,#&FC000003      ;Get the returned PSR bits
1107                 ORR     R2,R3,R10               ;Mix 'em into the PC
1108                 B       ae__return              ;And carry on the good work
1109
1110 90ae__swi       STMFD   R13!,{R0-R2}            ;Save what I must preserve
1111
1112                 LDR     R5,=Stream_Write0 :OR: &EF000000
1113                 TST     R0,#&00020000           ;Is the X bit set?
1114                 ORRNE   R5,R5,#&00020000        ;Yes -- set out one too
1115
1116                 LDR     R14,ae__swiRet          ;Get the special return instr
1117                 STMFD   R13!,{R5,R14}           ;Save this on the stack
1118                 MOV     R12,R13                 ;Preserve stack ptr in R12
1119                 LDR     R13,[R1,#13*4]          ;Load user's stack pointer
1120                 BIC     R0,R2,#&FC000003        ;Get the string address...
1121                 ADD     R0,R0,#4                ;... it's just after the SWI
1122                 MOV     R11,PC                  ;Set up return address oddly
1123                 MOV     PC,R12                  ;Call the SWI instruction
1124
1125                 MOV     R10,PC                  ;Get the processor flags
1126                 ADD     R13,R12,#8              ;Restore the stack pointer
1127                 MOV     R3,R0                   ;Get the string start ptr
1128
1129 95ae__swi       LDRB    R14,[R3],#1             ;Get a byte from the string
1130                 CMP     R14,#0                  ;Is it a null?
1131                 BNE     %95ae__swi              ;No -- jump round again
1132                 ADD     R3,R3,#3                ;Word align the result
1133                 BIC     R3,R3,#3
1134
1135                 LDMFD   R13!,{R0-R2}            ;Reload our important regs
1136                 AND     R14,R2,#3               ;Get the processor mode
1137                 CMP     R14,#SVC_mode           ;Are we in SVC mode?
1138                 ADDEQ   R14,R2,#4               ;Yes -- make a bogus value
1139                 STREQ   R14,[R1,#14*4]          ;And save over his R14 value
1140
1141                 ADD     R3,R3,#3                ;Word align the string end
1142                 BIC     R3,R3,#3                ;To find the next instruction
1143                 AND     R10,R2,#&FC000003       ;Get the (preserved) PSR bits
1144                 ORR     R2,R3,R10               ;Mix 'em into the PC
1145                 B       ae__return              ;And carry on the good work
1146
1147 70ae__swi       ORR     R2,R2,#3                ;Set the mode to SVC
1148                 BIC     R2,R2,#V_flag           ;Clear the V flag
1149                 B       ae__next                ;And move on to next instr
1150
1151 ae__swiRet      MOV     PC,R11                  ;My really odd return instr
1152
1153                 LTORG
1154
1155 ; --- ae__translateAddr ---
1156 ;
1157 ; On entry:     R0 == address to load from
1158 ;
1159 ; On exit:      R0 == translates the address
1160 ;
1161 ; Use:          Translates an address, allowing for horrible
1162 ;               things such as breakpoints
1163
1164 ae__translateAddr ROUT
1165
1166                 B       brkpt_translate         ;Get breakpoints to xlate
1167
1168 ;----- That's *all*, folks --------------------------------------------------
1169
1170                 END