chiark / gitweb /
Initial revision
[ssr] / StraySrc / Libraries / Core / s / flex
1 ;
2 ; flex.s
3 ;
4 ; Flexible memory handling (MDW)
5 ;
6 ; © 1994-1998 Straylight
7 ;
8
9 ;----- Licensing note -------------------------------------------------------
10 ;
11 ; This file is part of Straylight's flex.
12 ;
13 ; Flex 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 ; Flex 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 Flex.  If not, write to the Free Software Foundation,
25 ; 59 Temple Place - Suite 330, Boston, MA 02111-1307, USA.
26
27 ;----- New unified version --------------------------------------------------
28 ;
29 ; I'm finally fed up of maintaining four different versions of this code.
30 ; From now on, there is only this one.
31 ;
32 ; Lots of options are supported:
33 ;
34 ; OPT_APCS      Generate an APCS-compatible version
35 ; OPT_SAPPHIRE  Generate a Sapphire-compatible version
36 ; OPT_STEEL     Apply some STEEL-specific eccentricities
37 ; OPT_STANDALONE Build a standalone assembler version (default)
38 ; OPT_DUMP      Generate flex_dump code
39 ; OPT_DYNAREA   Generate dynamic-area handling code
40 ; OPT_STACK     Generate relocation stack handling code
41 ; OPT_DLL       Generate absolute address relocation for DLL code
42 ; OPT_ATEXIT    Register cleanup function with `atexit' for DLL code
43 ;
44 ;                                                               [mdw]
45
46 ;----- Set up some options --------------------------------------------------
47
48                 MACRO
49                 DCLOPT  $var
50                 [       :DEF:$var
51 $var            SETL    {TRUE}
52                 |
53                 GBLL    $var
54 $var            SETL    {FALSE}
55                 ]
56                 MEND
57
58                 DCLOPT  OPT_APCS
59                 DCLOPT  OPT_SAPPHIRE
60                 DCLOPT  OPT_STEEL
61                 DCLOPT  OPT_STANDALONE
62                 DCLOPT  OPT_DUMP
63                 DCLOPT  OPT_DYNAREA
64                 DCLOPT  OPT_STACK
65                 DCLOPT  OPT_DLL
66                 DCLOPT  OPT_ATEXIT
67
68         [ :LNOT:OPT_APCS:LAND::LNOT:OPT_SAPPHIRE:LAND::LNOT:OPT_STANDALONE
69                 GBLL    OPT_STANDALONE
70 OPT_STANDALONE  SETL    {TRUE}
71         ]
72
73 ;----- Standard stuff -------------------------------------------------------
74
75                 GET     libs:header
76                 GET     libs:swis
77
78 ;----- External dependencies ------------------------------------------------
79
80         [ OPT_SAPPHIRE
81                 GET     sapphire:fastMove
82                 GET     sapphire:event
83                 GET     sapphire:except
84                 GET     sapphire:libOpts
85                 GET     sapphire:roVersion
86                 GET     sapphire:sapphire
87         |
88                 IMPORT  fastMove
89         ]
90
91         [ OPT_DLL:LAND:OPT_APCS
92                 IMPORT  atexit
93         ]
94
95 ;----- Workspace macros -----------------------------------------------------
96
97         [ OPT_APCS
98
99                 MACRO
100 $label          WSPACE  $addr,$reg
101                 LCLS    r
102                 [       "$reg"=""
103 r               SETS    "R12"
104                 |
105 r               SETS    "$reg"
106                 ]
107                 ALIGN
108 $label
109                 LDR     $r,$addr
110                 [       OPT_DLL
111                 LDR     R14,[R10,#-536]
112                 ADD     $r,R14,$r
113                 ]
114                 MEND
115
116         ]
117
118 ;----- Main code ------------------------------------------------------------
119
120         [ OPT_SAPPHIRE
121                 AREA    |Sapphire$$Code|,CODE,READONLY
122         ]
123         [ OPT_APCS
124                 AREA    |C$$Code|,CODE,READONLY
125         ]
126         [ OPT_STANDALONE
127                 AREA    |Straylight$$Code|,CODE,READONLY
128         ]
129
130 ; --- flex__setslot ---
131 ;
132 ; On entry:     R0 == limit address of slot required, or -1 to read
133 ;
134 ; On exit:      R0 == actual address (after update)
135 ;               R1 == limit requested (R0 on entry)
136 ;
137 ; Use:          Sets the application's WimpSlot to a given value.  The value
138 ;               is given as an address, rather than as a size, which is
139 ;               the more normal way of doing things.
140 ;
141 ;               Since updated to cope with dynamic areas.
142
143 flex__setslot   ROUT
144
145                 STMFD   R13!,{R2-R6,R14}        ;Save some registers
146                 LDR     R14,flex__flags         ;Load interesting flags
147         [ OPT_DYNAREA
148                 TST     R14,#fFlag__dynArea     ;Using a dynamic area?
149                 BNE     %50flex__setslot        ;Yes -- do different things
150         ]
151
152                 ; --- Change the WimpSlot ---
153                 ;
154                 ; Be careful -- we may be sharing memory space with another
155                 ; application!
156
157                 MOV     R5,R0                   ;Look after my argument
158                 MOV     R0,#14                  ;Read app space value
159                 MOV     R1,#0                   ;Read, rather than write
160                 SWI     XOS_ChangeEnvironment   ;Read the value
161                 MOV     R3,R1                   ;Keep hold of app space size
162
163                 MOV     R0,#0                   ;Now read memory limit
164                 MOV     R1,#0                   ;Read again, not write
165                 SWI     XOS_ChangeEnvironment   ;Read memory limit
166                 MOV     R6,R1                   ;Look after memory limit
167
168                 CMP     R6,R3                   ;How does this shape up?
169                 MOVLT   R1,R3                   ;If too low, extend mem limit
170                 SWILT   XOS_ChangeEnvironment   ;Set memory limit
171
172                 CMP     R5,#-1                  ;Does he want to read it?
173                 MOVEQ   R0,R5                   ;Yes -- do that then
174                 SUBNE   R0,R5,#&8000            ;Otherwise work out slot size
175                 MOV     R1,#-1                  ;Not interested in next slot
176                 SWI     XWimp_SlotSize          ;Change the WimpSlot value
177                 MOV     R4,R0                   ;Look after updated value
178
179                 CMP     R6,R3                   ;If we changed the mem limit
180                 MOVLT   R1,R6                   ;Put it back the way it was
181                 MOVLT   R0,#0                   ;Setting memory limit
182                 SWILT   XOS_ChangeEnvironment   ;Restore memory limit
183
184                 ADD     R0,R4,#&8000            ;New value of WimpSlot
185                 MOV     R1,R5                   ;Return requested size too
186                 LDMFD   R13!,{R2-R6,PC}^        ;Return to caller
187
188                 ; --- Change a dynamic area size ---
189
190         [ OPT_DYNAREA
191
192 50flex__setslot MOV     R2,R0                   ;Look after address requested
193                 LDR     R3,flex__end            ;Find the end address
194                 SUBS    R1,R2,R3                ;Work out the difference
195                 LDR     R0,flex__dynArea        ;Load dynamic area handle
196                 SWI     XOS_ChangeDynamicArea   ;Try and change the size
197                 ADDGT   R0,R3,R1                ;Get new limit address
198                 SUBLE   R0,R3,R1                ;Irritatingly positive...
199                 MOV     R1,R2                   ;And the caller's request
200                 LDMFD   R13!,{R2-R6,PC}^        ;Return to caller
201
202         ]
203
204                 LTORG
205
206 ; --- flex__fixup ---
207 ;
208 ; On entry:     --
209 ;
210 ; On exit:      --
211 ;
212 ; Use:          Goes off and fixes up all the anchors currently pointing at
213 ;               blocks in the heap
214
215 flex__fixup     ROUT
216
217                 STMFD   R13!,{R0-R3,R14}        ;Save some registers
218
219                 ; --- Set up for the fixup loop ---
220
221                 LDR     R1,flex__base           ;Find the base of the heap
222                 LDR     R2,flex__free           ;Find end of the blocks
223
224                 ; --- Now go through and fix things up ---
225
226 00flex__fixup   CMP     R1,R2                   ;Have we reached the end yet?
227                 LDMGEFD R13!,{R0-R3,PC}^        ;Return to caller if so
228                 LDR     R3,[R1,#flex__bkanchor] ;Find the pointer to anchor
229                 CMP     R3,#0                   ;Is the block currently free?
230                 ADDNE   R14,R1,#flex__ohead     ;No -- bump aver the overhead
231                 STRNE   R14,[R3]                ;And store in the anchor
232                 LDR     R3,[R1,#flex__size]     ;Find the block's size
233                 ADD     R3,R3,#flex__ohead+7    ;Add on the extra overhead
234                 BIC     R3,R3,#7                ;And word align the size
235                 ADD     R1,R1,R3                ;Bump along to the next block
236                 B       %00flex__fixup          ;And fix that one up too
237
238                 LTORG
239
240 ; --- flex__compact ---
241 ;
242 ; On entry:     --
243 ;
244 ; On exit:      --
245 ;
246 ; Use:          Try to compact the heap by one iteration
247 ;
248 ;               We troll through the blocks to find a free one and haul
249 ;               everything down a bit
250
251 flex__compact   ROUT
252
253                 STMFD   R13!,{R0-R6,R14}        ;Save some registers
254
255                 ; --- Set up for a loop through the data ---
256
257                 LDR     R5,flex__base           ;Find the beginning of flex
258                 LDR     R1,flex__free           ;Find the end too
259
260                 ; --- Find a free block ---
261
262 00flex__compact CMP     R5,R1                   ;Are we at the end yet?
263                 BGE     %10flex__compact        ;Yes -- the heap is compact
264
265                 LDR     R2,[R5,#flex__bkanchor] ;Get the block's anchor addr
266                 CMP     R2,#0                   ;Is the block free?
267                 LDR     R2,[R5,#flex__size]     ;Get the block size
268                 ADD     R2,R2,#flex__ohead+7    ;Add on the overhead bytes
269                 BIC     R2,R2,#7                ;And word align the size
270                 ADDNE   R5,R5,R2                ;No -- move on to next one
271                 BNE     %00flex__compact        ;And go round for another one
272
273                 ; --- We've found a free block ---
274
275 01flex__compact ADD     R6,R5,R2                ;Point to the next block
276                 CMP     R6,R1                   ;Is that the end of the heap?
277                 BGE     %05flex__compact        ;Yes -- reduce the free ptr
278
279                 ; --- Check for two free blocks together ---
280
281                 LDR     R0,[R6,#flex__bkanchor] ;Does this have an anchor?
282                 CMP     R0,#0                   ;Check if it's free
283                 BNE     %02flex__compact        ;No -- start swapping blocks
284
285                 ; --- Join two adjacent free blocks together ---
286
287                 LDR     R0,[R6,#flex__size]     ;Yes -- get its size
288                 ADD     R2,R0,R2                ;Concatenate the two blocks
289                 ADD     R2,R2,#flex__ohead+7    ;Add on the overhead bytes
290                 BIC     R2,R2,#7                ;And word align the size
291                 B       %01flex__compact        ;And check again...
292
293                 ; --- There's a block to bring down ---
294
295 02flex__compact LDR     R4,[R6,#flex__size]     ;Get size of block to move
296                 ADD     R4,R4,#flex__ohead+7    ;Add the flex overhead
297                 BIC     R4,R4,#7                ;And word align the size
298                 MOVS    R2,R4                   ;This is the size to move
299                 MOV     R0,R5                   ;Where to move it to
300                 MOV     R1,R6                   ;Where it is right now
301                 BLNE    fastMove                ;Copy it down PDQ
302         [ OPT_STACK
303                 BLNE    flex__reloc             ;Deal with the relocation
304         ]
305                 ADD     R0,R5,R4                ;Point after block we moved
306                 MOV     R1,#0                   ;Block doesn't have an anchor
307                 STR     R1,[R0,#flex__bkanchor] ;Store that away for later
308                 SUB     R1,R6,R5                ;Find the difference here
309                 SUB     R1,R1,#flex__ohead      ;Don't count this size here
310                 STR     R1,[R0,#flex__size]     ;Store the old size in free
311
312                 ; --- We need to fix up the block we moved ---
313
314                 LDR     R0,[R5,#flex__bkanchor] ;Get the anchor pointer
315                 ADD     R1,R5,#flex__ohead      ;Point to the real data
316                 STR     R1,[R0]                 ;Store client's new anchor
317
318                 ; --- That's it -- return to caller ---
319
320                 LDMFD   R13!,{R0-R6,PC}^        ;Return to caller
321
322                 ; --- Merge the last block with the free area ---
323
324 05flex__compact STR     R5,flex__free           ;This is the new free area
325                 LDR     R0,flex__chunk          ;Get the machine page size
326                 SUB     R0,R0,#1                ;Turn into a bitmask
327                 ADD     R5,R5,R0                ;Align this to page boundary
328                 BIC     R0,R5,R0                ;And finish off the align
329                 LDR     R1,flex__end            ;Find the end of the heap
330                 CMP     R0,R1                   ;Are these different?
331                 BLNE    flex__setslot           ;Yes -- free some memory
332                 STRNE   R0,flex__end            ;Store the end away
333
334                 ; --- That's it -- return ---
335
336                 LDMFD   R13!,{R0-R6,PC}^        ;Return to caller
337
338                 ; --- There wasn't anything to do -- we're compacted ---
339
340 10flex__compact LDR     R0,flex__flags
341                 ORR     R0,R0,#fFlag__compact   ;We are now compacted
342                 STR     R0,flex__flags
343                 LDMFD   R13!,{R0-R6,PC}^        ;Return to caller
344
345                 LTORG
346
347 ; --- flex_reduce ---
348 ;
349 ; On entry:     --
350 ;
351 ; On exit:      --
352 ;
353 ; Use:          Compacts the flex heap by one iteration.
354
355                 EXPORT  flex_reduce
356 flex_reduce     ROUT
357
358                 STMFD   R13!,{R0,R12,R14}       ;Stack some registers
359                 WSPACE  flex__wSpace            ;Find my workspace
360
361                 ; --- Check if it's compacted ---
362
363                 LDR     R0,flex__flags          ;Get my nice flags word
364                 TST     R0,#fFlag__compact      ;Is the heap compacted?
365                 BLEQ    flex__compact           ;No -- compact it a bit
366                 LDMFD   R13!,{R0,R12,PC}^       ;Return to caller now
367
368                 LTORG
369
370 ; --- flex_compact ---
371 ;
372 ; On entry:     --
373 ;
374 ; On exit:      --
375 ;
376 ; Use:          Completely compacts the flex heap.
377
378                 EXPORT  flex_compact
379 flex_compact    ROUT
380
381                 STMFD   R13!,{R0,R12,R14}       ;Save some registers
382                 WSPACE  flex__wSpace            ;Find my workspace
383
384                 ; --- Compaction loop ---
385
386 00flex_compact  LDR     R0,flex__flags          ;Get my nice flags word
387                 TST     R0,#fFlag__compact      ;Is the heap compacted?
388                 BLEQ    flex__compact           ;No -- compact another stage
389                 BEQ     %00flex_compact         ;And go round again
390
391                 ; --- The end -- return ---
392
393                 LDMFD   R13!,{R0,R12,PC}^       ;Return to caller
394
395                 LTORG
396
397 ; --- flex_free ---
398 ;
399 ; On entry:     R0 == pointer to the flex anchor
400 ;
401 ; On exit:      --
402 ;
403 ; Use:          Frees a flex block allocated by flex_alloc.
404
405                 EXPORT  flex_free
406 flex_free       ROUT
407
408                 STMFD   R13!,{R0,R12,R14}       ;Save some registers
409                 WSPACE  flex__wSpace
410
411                 ; --- Mark the block as being free ---
412
413                 LDR     R14,[R0]                ;Get pointer to actual block
414                 MOV     R0,#0
415                 STR     R0,[R14,#flex__bkanchor-flex__ohead]
416
417                 ; --- Update the flags -- not compacted any more ---
418
419                 LDR     R0,flex__flags          ;Get my nice flags word
420                 BIC     R0,R0,#fFlag__compact   ;We are no longer compacted
421                 STR     R0,flex__flags          ;Store it back
422
423                 LDMFD   R13!,{R0,R12,PC}^       ;Return to caller
424
425                 LTORG
426
427 ; --- flex_alloc ---
428 ;
429 ; On entry:     R0 == pointer to a flex anchor
430 ;               R1 == desired size of flex block
431 ;
432 ; On exit:      Sapphire: CS if no memory could be allocated, CC otherwise
433 ;               APCS: R0 zero if no memory, nonzero otherwise
434 ;
435 ; Use:          Allocates a block in the shifting heap.
436
437                 EXPORT  flex_alloc
438 flex_alloc      ROUT
439
440         [ OPT_APCS
441                 STMFD   R13!,{R4,R5,R12,R14}    ;Save some registers
442         |
443                 STMFD   R13!,{R0-R5,R12,R14}    ;Save some registers
444         ]
445
446                 WSPACE  flex__wSpace
447
448                 ; --- Round up the size etc. ---
449
450                 MOV     R4,R0                   ;Keep the anchor pointer
451                 MOV     R3,R1                   ;Keep the actual size wanted
452                 ADD     R5,R1,#flex__ohead+7    ;Add on overhead for flex
453                 BIC     R5,R5,#7                ;And word-align the size
454
455                 ; --- See if there's enough space ---
456
457 00flex_alloc    LDR     R0,flex__free           ;Get the free pointer
458                 LDR     R2,flex__end            ;And the end of the block
459                 SUB     R1,R2,R0                ;How much room is left
460                 CMP     R1,R5                   ;Enough for the new block
461                 BGE     %10flex_alloc           ;Set up the block
462
463                 ; --- Not enough room in block - try to get some more ---
464
465                 ADD     R0,R0,R5                ;Find the new slot limit
466                 BL      flex__setslot           ;Set up the new slot
467                 CMP     R0,R1                   ;Did we get enough
468                 STRGE   R0,flex__end            ;Yes -- remember the new end
469                 LDRGE   R0,flex__free           ;Find the free area again
470                 BGE     %10flex_alloc           ;And allocate the memory
471
472                 ; --- Can we compact the heap? ---
473
474                 LDR     R0,flex__end            ;Get the old heap extent
475                 BL      flex__setslot           ;Put the slot back again
476                 LDR     R0,flex__flags          ;Get my current flags
477                 TST     R0,#fFlag__compact      ;Is the heap compact?
478                 BLEQ    flex_compact            ;No -- really compact it
479                 BEQ     %00flex_alloc           ;And give it another go
480
481                 ; --- We couldn't get enough memory at all ---
482
483         [ OPT_APCS
484                 MOV     R0,#0
485                 LDMFD   R13!,{R4,R5,R12,PC}^    ;Restore registers
486         |
487                 LDMFD   R13!,{R0-R5,R12,R14}    ;Restore registers
488                 ORRS    PC,R14,#C_flag          ;Set C flag to indicate fail
489         ]
490
491                 ; --- Set up the block pointed to by R0
492
493 10flex_alloc    STR     R4,[R0,#flex__bkanchor] ;Set up the back anchor
494                 STR     R3,[R0,#flex__size]     ;Remember size of this block
495                 ADD     R1,R0,#flex__ohead      ;Point to real data block
496                 STR     R1,[R4]                 ;Let user know where block is
497                 ADD     R1,R0,R5                ;Get the new free pointer
498                 STR     R1,flex__free           ;Store the new free ptr
499
500                 ; --- Return to the user ---
501
502         [ OPT_APCS
503                 MOV     R0,#-1
504                 LDMFD   R13!,{R4,R5,R12,PC}^
505         |
506                 LDMFD   R13!,{R0-R5,R12,R14}
507                 BICS    PC,R14,#C_flag
508         ]
509
510                 LTORG
511
512 ; --- flex_size ---
513 ;
514 ; On entry:     R0 == pointer to flex anchor
515 ;
516 ; On exit:      R0 == size of allocated block
517 ;
518 ; Use:          Reads the size of a flex block.
519
520                 EXPORT  flex_size
521 flex_size       ROUT
522
523                 LDR     R0,[R0]                 ;Get the flex block
524                 LDR     R0,[R0,#flex__size-flex__ohead]
525                 MOVS    PC,R14
526
527                 LTORG
528
529 ; --- flex_extend ---
530 ;
531 ; On entry:     R0 == pointer to flex anchor
532 ;               R1 == new size of block to set
533 ;
534 ; On exit:      CS if it failed due to lack of memory, CC otherwise
535 ;
536 ; Use:          Alters the size of a block to the given value.
537
538                 EXPORT  flex_extend
539 flex_extend     ROUT
540
541                 STMFD   R13!,{R1,R2,R14}
542
543                 ; --- Be *very* careful to preserve the flags... ---
544
545                 MOV     R2,R1
546                 LDR     R1,[R0]
547                 LDR     R1,[R1,#flex__size-flex__ohead]
548                 SUB     R2,R2,R1
549                 BL      flex_midExtend
550
551                 ; --- Note ---
552                 ;
553                 ; We preserved the flags above, and midExtend should do
554                 ; its bit to help, so we can just return with the flags
555                 ; set by midExtend.  Easy, no?
556
557                 LDMFD   R13!,{R1,R2,PC}
558
559                 LTORG
560
561 ; --- flex_midExtend ---
562 ;
563 ; On entry:     R0 == pointer to a flex anchor
564 ;               R1 == `at' -- position in block to extend from
565 ;               R2 == `by' -- how many bytes to extend (may be -ve)
566 ;
567 ; On exit:      Sapphire: CS if not enough memory, CC otherwise
568 ;               APCS: R0 zero if not enough memory, nonzero otherwise
569 ;
570 ; Use:          Either creates a gap in a block (by>0) or deletes bytes
571 ;               from a block.  This is always done in such a way that the
572 ;               byte originally at offset `at' is now at offset `at'+`by'.
573
574                 EXPORT  flex_midExtend
575                 EXPORT  flex_midextend
576 flex_midExtend  ROUT
577 flex_midextend
578
579                 ; --- A bit of clever setting up ---
580
581         [ OPT_APCS
582                 TEQ     R2,#0                   ;Move by zero bytes?
583                 MOVEQ   R0,#-1                  ;Yes, it worked
584                 MOVEQS  PC,R14                  ;And return
585                 STMFD   R13!,{R12,R14}          ;Otherwise save registers
586         |
587                 BIC     R14,R14,#C_flag         ;Clear C now
588                 STMFD   R13!,{R12,R14}          ;Save R14 on the stack
589                 TEQ     R2,#0                   ;Move by zero bytes?
590                 LDMEQFD R13!,{R12,PC}^          ;Yes -- don't bother then
591         ]
592
593                 ; --- Save some more registers and find workspace ---
594
595                 WSPACE  flex__wSpace
596
597                 ; --- Find out what we have to do depending on `by' ---
598
599                 CMP     R2,#0                   ;Is it +ve or -ve?
600                 BGT     %50flex_midExtend       ;If we must extend, do that
601
602                 ; --- We reduce the block size -- easy ---
603
604         [ OPT_APCS
605                 STMFD   R13!,{R4}
606         |
607                 STMFD   R13!,{R0-R4}            ;Save some more registers
608         ]
609                 MOV     R3,R2                   ;Keep the size safe
610                 MOV     R14,R1                  ;Keep `at' safe too
611
612                 LDR     R4,[R0]                 ;Get the actual block ptr
613                 ADD     R1,R4,R14               ;Copy from `at'
614                 ADD     R0,R1,R2                ;Copy to `at'-|`by'|
615                 LDR     R2,[R4,#flex__size-flex__ohead]
616                 SUBS    R2,R2,R14               ;Size of block - `at'
617                 BLNE    fastMove                ;Copy the area down
618         [ OPT_STACK
619                 BLNE    flex__reloc             ;And relocate the stack
620         ]
621
622                 ; --- Find the new actual and logical sizes ---
623
624                 SUB     R4,R4,#flex__ohead      ;Point to my actual data
625                 LDR     R0,[R4,#flex__size]     ;Get the size of the block
626                 ADD     R1,R0,R3                ;Find new adjusted size
627                 STR     R1,[R4,#flex__size]     ;This is new logical size
628                 ADD     R0,R0,#flex__ohead+7    ;Add the overhead to both...
629                 ADD     R1,R1,#flex__ohead+7    ;... of these sizes and...
630                 BIC     R0,R0,#7                ;... align to heap...
631                 BIC     R1,R1,#7                ;... granularity nicely
632
633                 ; --- If these are different, insert a free block ---
634
635                 SUBS    R0,R0,R1                ;Is there space for free blk?
636                 BLE     %00flex_midExtend       ;No -- just wrap up nicely
637
638                 ; --- Insert the free block here ---
639
640                 ADD     R2,R4,R1                ;Find the free block
641                 SUB     R0,R0,#flex__ohead      ;Subtract the overhead
642                 STR     R0,[R2,#flex__size]     ;And store `logical' size
643                 MOV     R0,#0                   ;This block has no owner
644                 STR     R0,[R2,#flex__bkanchor] ;So store a null anchor
645
646                 ; --- There's a free block -- enable compaction ---
647
648                 LDR     R1,flex__flags          ;Load my current flags
649                 BIC     R1,R1,#fFlag__compact   ;We're not compact any more
650                 STR     R1,flex__flags          ;Store the flags back again
651
652                 ; --- Return to caller ---
653
654 00flex_midExtend
655         [ OPT_APCS
656                 MOV     R0,#-1
657                 LDMFD   R13!,{R4,R12,PC}^
658         |
659                 LDMFD   R13!,{R0-R4,R12,PC}^    ;Smile, smile, smile
660         ]
661
662                 ; --- Work out how much extra space we need ---
663
664 50flex_midExtend
665         [ OPT_APCS
666                 STMFD   R13!,{R4-R9}
667         |
668                 STMFD   R13!,{R0-R9}            ;Save yet more registers
669         ]
670
671                 ; --- Take copies of the arguments ---
672
673                 MOV     R4,R0
674                 MOV     R5,R1
675                 MOV     R6,R2
676
677                 LDR     R7,[R4]                 ;Find the actual flex block
678                 SUB     R7,R7,#flex__ohead      ;Point to my data
679                 LDR     R3,[R7,#flex__size]     ;Find the size of the block
680
681                 ADD     R2,R3,#7                ;Don't add in overhead
682                 BIC     R2,R2,#7                ;How much space in this block
683                 SUB     R1,R2,R3                ;R1 == dead space at the end
684                 SUBS    R1,R6,R1                ;R1 == extra space needed
685
686                 ; --- Can we do it within the block? ---
687
688                 ADDLE   R3,R3,R6                ;Increase the size
689                 STRLE   R3,[R7,#flex__size]     ;And store
690                 BLE     %70flex_midExtend       ;Yes -- just shuffle it about
691
692                 ; --- We need to find R1 more bytes from somewhere ---
693                 ;
694                 ; Our strategy here is fairly simple, really (although we
695                 ; could refine it a lot, I suppose).
696                 ;
697                 ; 1. Find as many free blocks at the end of the midExtend
698                 ;    block as possible, join them all together and see if
699                 ;    that will do.
700                 ;
701                 ; 2. If not, we just flex_alloc a block of the right size
702                 ;    and shift everything skywards.
703
704                 ; --- This calls for some serious register allocation ---
705                 ;
706                 ; R1 == the amount of extra we need (round up to size)
707                 ; R2 == pointer to blocks for loop
708                 ;
709                 ; R4 == address of anchor of midExtend block
710                 ; R5 == point at which we need to extend it
711                 ; R6 == how much we extend it by
712                 ; R7 == pointer to the actual block
713                 ; R8 == pointer to next block after midExtend one
714                 ; R9 == the size we've accumulated so far
715
716                 ; --- Start the loop (I want to get off) ---
717
718                 ADD     R1,R1,#7                ;Align the size to multiple
719                 BIC     R1,R1,#7
720                 MOV     R9,#0                   ;We haven't found any yet
721                 ADD     R8,R7,R2                ;Point almost to next block
722                 ADD     R8,R8,#flex__ohead      ;Point to it properly
723                 MOV     R2,R8                   ;Start the loop here
724
725                 LDR     R3,flex__free           ;Find the free area start
726
727                 ; --- Find free blocks now ---
728
729 55flex_midExtend
730                 CMP     R2,R3                   ;Are we at the end yet?
731                 BGE     %65flex_midExtend       ;Oh, well -- we're stuffed
732                 LDR     R14,[R2,#flex__bkanchor] ;Is this block free?
733                 CMP     R14,#0                  ;Quick check McCheck
734                 BNE     %65flex_midExtend       ;Oh, well -- we're stuffed
735                 LDR     R14,[R2,#flex__size]    ;Get the block's size
736                 ADD     R14,R14,#flex__ohead+7  ;Add on the overhead area
737                 BIC     R14,R14,#7              ;And align to doubleword
738                 ADD     R9,R9,R14               ;Accumulate the block size
739                 CMP     R9,R1                   ;Have we got enough yet?
740                 BGE     %60flex_midExtend       ;That's it -- we've got it
741                 ADD     R2,R2,R14               ;Move onto the next block
742                 B       %55flex_midExtend       ;And check the next one
743
744                 ; --- We got enough free blocks to save us ---
745
746 60flex_midExtend
747                 LDR     R0,[R7,#flex__size]     ;Get the current size of this
748                 ADD     R0,R0,R6                ;Add on the extended size
749                 STR     R0,[R7,#flex__size]     ;And put it back again
750                 BEQ     %70flex_midExtend       ;If perfect fit, don't create
751
752                 ; --- Create a new free block to use up the space ---
753
754                 ADD     R0,R8,R1                ;Point to the new free block
755                 SUB     R2,R9,R1                ;Find out how much is over
756                 SUB     R2,R2,#flex__ohead      ;Don't want to count that
757                 STR     R2,[R0,#flex__size]     ;Store the size away
758                 MOV     R2,#0                   ;This block is not used
759                 STR     R2,[R0,#flex__bkanchor] ;So don't give it an anchor
760                 B       %70flex_midExtend       ;And do the shuffling about
761
762                 ; --- There wasn't enough space there, so allocate more ---
763
764 65flex_midExtend
765                 MOV     R9,R1                   ;Look after the size we want
766                 SUB     R13,R13,#4              ;Create a flex anchor
767                 MOV     R0,R13                  ;Point to it
768                 SUB     R1,R1,#flex__ohead      ;We'll overwrite the overhead
769                 BL      flex_alloc              ;Allocate some memory
770         [ OPT_APCS
771                 CMP     R0,#0                   ;Did it fail?
772                 ADDEQ   R13,R13,#1              ;Skip past stacked anchor
773                 LDMEQFD R13!,{R4-R9,R12,PC}^
774         |
775                 LDMCSFD R13!,{R0-R9,R12,R14}    ;If it failed, unstack...
776                 ADDCS   R13,R13,#1              ;Skip past stacked anchor
777                 ORRCSS  PC,R14,#C_flag          ;... and set carry
778         ]
779                 LDR     R3,[R13],#4             ;Get pointer to new block
780
781                 ; --- A reminder about the registers ---
782                 ;
783                 ; R0-R2 aren't interesting any more
784                 ; R3 points flex__ohead bytes ahead of old flex__free
785                 ; R4-R6 are still our arguments
786                 ; R7,R8 aren't exciting any more
787                 ; R9 is the amount of extra space we wanted
788
789                 ; --- Our block may have moved -- recalculate next ptr ---
790
791                 LDR     R7,[R4]                 ;Point to the block
792                 SUB     R7,R7,#flex__ohead      ;Point to the overhead area
793                 LDR     R8,[R7,#flex__size]     ;Get the size of the block
794                 ADD     R8,R8,#flex__ohead+7    ;Bump over the overhead
795                 BIC     R8,R8,#7                ;And align to multiple of 8
796
797                 ; --- Move all the other blocks up a bit ---
798
799                 ADD     R1,R7,R8                ;Start moving from here
800                 ADD     R0,R1,R9                ;Move it to here
801                 SUB     R2,R3,#flex__ohead      ;Find the old flex__free
802                 SUBS    R2,R2,R1                ;Copy the right section up
803                 BLNE    fastMove
804         [ OPT_STACK
805                 BLNE    flex__reloc             ;And adjust any stacked ptrs
806         ]
807
808                 ; --- Adjust the block size and anchors ---
809
810                 LDR     R14,[R7,#flex__size]    ;Get the size of this block
811                 ADD     R14,R14,R6              ;Add on the extension
812                 STR     R14,[R7,#flex__size]    ;Store it back again
813                 BL      flex__fixup             ;Fix up all the anchors again
814                 ; Drop through to block shuffling
815
816                 ; --- Create the gap in the flex block ---
817
818 70flex_midExtend
819                 LDR     R4,[R7,#flex__size]     ;Get the size of the block
820                 SUB     R4,R4,R6                ;Find the old length
821                 ADD     R1,R7,#flex__ohead      ;Point to the real data
822                 ADD     R1,R1,R5                ;Find the `at' position
823                 ADD     R0,R1,R6                ;Find the `at'+|`by'| posn
824                 SUBS    R2,R4,R5                ;Find the length to move
825                 BLNE    fastMove                ;Do the move
826         [ OPT_STACK
827                 BLNE    flex__reloc             ;And adjust any stacked ptrs
828         ]
829
830         [ OPT_APCS
831                 MOV     R0,#-1
832                 LDMFD   R13!,{R4-R9,R12,PC}^
833         |
834                 LDMFD   R13!,{R0-R9,R12,PC}^
835         ]
836
837                 LTORG
838
839 ; --- flex_init ---
840 ;
841 ; On entry:     R0 == pointer to dynamic area name, or zero
842 ;               R1 == maximum allowed size of the area
843 ;                       (except Sapphire version)
844 ;
845 ; On exit:      --
846 ;
847 ; Use:          Initialises the flex heap for use.
848
849                 EXPORT  flex_init
850                 EXPORT  flex_dinit
851 flex_init       ROUT
852
853         [ OPT_STEEL
854                 MOV     R0,#0
855                 MOV     R1,#1
856         ]
857
858 flex_dinit      STMFD   R13!,{R0-R8,R12,R14}
859                 WSPACE  flex__wSpace
860
861         [ :LNOT:OPT_STANDALONE
862
863                 ; --- Prevent multiple initialisation ---
864
865                 LDR     R14,flex__flags         ;Find my flags word
866                 TST     R14,#fFlag__inited      ;Am I initialised yet?
867                 LDMNEFD R13!,{R0-R8,R12,PC}^    ;Yes -- return right now
868
869         ]
870
871   [ OPT_DYNAREA
872
873                 ; --- If this is Sapphire, find the options block ---
874
875         [ OPT_SAPPHIRE
876
877                 BL      rov_init                ;Work out the RISC OS version
878                 BL      rov_version             ;Get the version
879                 CMP     R0,#348                 ;Is this RISC OS 3.5?
880                 BCC     %10flex_init            ;No -- skip ahead then
881
882                 LDR     R0,flex__optName        ;Get the magic marker word
883                 BL      libOpts_find            ;Try to find the options
884                 BCC     %10flex_init            ;Not there -- skip on then
885                 LDR     R14,[R0,#0]             ;Load the flags out
886                 TST     R14,#1                  ;Is the dynamic area flag on?
887                 BEQ     %10flex_init            ;No -- don't do this then
888
889                 ; --- See if we can create a dynamic area ---
890
891                 TST     R14,#2                  ;Specified area size?
892                 LDRNE   R5,[R0,#4]              ;Yes -- load from opts block
893                 MOVEQ   R5,#16*1024*1024        ;16 meg maximum size
894                 LDR     R8,sapph_appName        ;Find the application name
895
896         |
897
898                 ; --- If this is APCS, then use the arguments ---
899
900                 CMP     R0,#0                   ;Is a dynamic area wanted?
901                 CMPNE   R1,#0                   ;Just check for stupidity
902                 BEQ     %10flex_init            ;No -- then skip ahead
903                 MOV     R8,R0                   ;Find the name pointer
904                 MOV     R5,R1                   ;And the size requested
905
906                 MOV     R0,#129                 ;Find the OS version
907                 MOV     R1,#0                   ;Convoluted call for this...
908                 MOV     R2,#255                 ;No idea why
909                 SWI     OS_Byte                 ;Call the operating system
910                 CMP     R1,#&A5                 ;Is it late enough?
911                 BCC     %10flex_init            ;No -- ignore the request
912
913         ]
914
915                 ; --- Create a dynamic area ---
916
917                 MOV     R0,#0                   ;Create new dynamic area
918                 MOV     R1,#-1                  ;Give me any old number
919                 MOV     R2,#0                   ;Zero size initially
920                 MOV     R3,#-1                  ;Don't care about base addr
921                 MOV     R4,#(1<<7)              ;Don't let user drag the bar
922                 MOV     R6,#0                   ;No dynamic area handler
923                 MOV     R7,#0                   ;I wuz told to do this
924                 SWI     XOS_DynamicArea         ;Try to create the area
925                 BVS     %10flex_init            ;It failed -- use WimpSlot
926
927                 ; --- Set up workspace for this ---
928
929                 STR     R3,flex__base           ;Store base of the area
930                 STR     R3,flex__free           ;The first free part
931                 STR     R3,flex__end            ;And the end
932                 STR     R1,flex__dynArea        ;Save dynamic area handle
933
934                 MOV     R0,#fFlag__compact + fFlag__inited + fFlag__dynArea
935                 STR     R0,flex__flags          ;Store the appropriate flags
936
937                 ; --- Add in tidy-up routine to delete the area ---
938
939         [ OPT_SAPPHIRE
940                 BL      except_init             ;We need to clear it up
941                 ADR     R0,flex__exit           ;Point to exit handler
942                 MOV     R1,R12                  ;Pass it my workspace
943                 BL      except_atExit           ;Register the routine
944         ]
945
946         [ OPT_ATEXIT
947                 ADR     R0,flex_die             ;Point to exit handler
948                 BL      atexit                  ;And call that
949         ]
950
951                 B       %20flex_init            ;And continue initialisation
952
953   ]
954
955                 ; --- Find out the slot size ---
956
957 10flex_init     MOV     R0,#-1                  ;Read current slot size
958                 BL      flex__setslot           ;Do the slot thing
959
960                 ; --- Store initial heap information ---
961
962                 STR     R0,flex__base           ;The start of the heap
963                 STR     R0,flex__free           ;The first free part
964                 STR     R0,flex__end            ;And the end
965
966                 MOV     R0,#fFlag__compact + fFlag__inited
967                                                 ;Empty heaps is compact heaps
968                 STR     R0,flex__flags
969
970                 ; --- Get the page size of the machine ---
971
972 20flex_init     SWI     OS_ReadMemMapInfo       ;Get page size (in R0)
973                 STR     R0,flex__chunk          ;Store for future reference
974
975                 ; --- Set up the flex relocation stack ---
976
977         [ OPT_STACK
978                 ADR     R14,flex__relocStk      ;Point to the stack base
979                 STR     R14,flex__relocSP       ;Save this as initial SP
980         ]
981
982                 ; --- Register the flex compactor as a postfilter ---
983
984         [ OPT_SAPPHIRE
985                 BL      event_init              ;Initialise event system
986                 ADR     R0,flex__preFilter      ;Point to the prefilter
987                 MOV     R1,R12                  ;Give it my workspace ptr
988                 BL      event_preFilter         ;Add the filter into the list
989                 ADR     R0,flex__postFilter     ;Point to the postfilter
990                 MOV     R1,R12                  ;Give it my workspace ptr
991                 BL      event_postFilter        ;Add the filter into the list
992         ]
993
994                 LDMFD   R13!,{R0-R8,R12,PC}^
995
996         [ OPT_SAPPHIRE
997 flex__optName   DCB     "FLEX"
998         ]
999
1000                 LTORG
1001
1002         [ OPT_SAPPHIRE
1003 flex__wSpace    DCD     0
1004         ]
1005
1006         [ OPT_APCS
1007 flex__wSpace    DCD     flex__sSpace
1008         ]
1009
1010 ; --- flex__preFilter ---
1011 ;
1012 ; On entry:     R0 == WIMP event mask
1013 ;               R1 == pointer to event block
1014 ;               R2 == time to return, or 0
1015 ;               R3 == pointer to poll word if necessary
1016 ;
1017 ; On exit:      R0,R2 maybe updated to enable idle events
1018 ;
1019 ; Use:          Enables full idle events if the flex heap needs compacting.
1020
1021         [ OPT_SAPPHIRE
1022
1023 flex__preFilter ROUT
1024
1025                 STMFD   R13!,{R14}              ;Save a register
1026                 LDR     R14,flex__flags         ;Find the flags word
1027                 TST     R14,#fFlag__compact     ;Is the heap compacted?
1028                 BICEQ   R0,R0,#1                ;No -- unmask idle events
1029                 MOVEQ   R2,#0                   ;And return immediately
1030                 LDMFD   R13!,{PC}^              ;Return to caller
1031
1032                 LTORG
1033
1034         ]
1035
1036 ; --- flex__postFilter ---
1037 ;
1038 ; On entry:     R0 == WIMP reason code
1039 ;               R1 == pointer to event block
1040 ;               R2 == time to return or 0
1041 ;               R3 == pointer to poll word or nothing really
1042 ;
1043 ; On exit:      Everything must be preserved
1044 ;
1045 ; Use:          Compacts the flex heap every idle event
1046
1047         [ OPT_SAPPHIRE
1048
1049 flex__postFilter ROUT
1050
1051                 CMP     R0,#0                   ;Is this an idle event?
1052                 MOVNES  PC,R14                  ;No -- then return right now
1053                 STMFD   R13!,{R0}               ;Save a register
1054                 LDR     R0,flex__flags          ;Find the flags word
1055                 TST     R0,#fFlag__compact      ;Is the heap compacted?
1056                 LDMFD   R13!,{R0}               ;Restore the register's value
1057                 MOVNES  PC,R14                  ;Return if it is
1058                 B       flex__compact           ;Go give the heap a nudge
1059
1060                 LTORG
1061
1062         ]
1063
1064         [ OPT_APCS
1065
1066 ; --- flex_budge / flex_dont_budge ---
1067 ;
1068 ; On entry:     --
1069 ;
1070 ; On exit:      --
1071 ;
1072 ; Use:          Nothing.  Both of these do the same thing.
1073
1074                 EXPORT  flex_budge
1075                 EXPORT  flex_dont_budge
1076 flex_budge      ROUT
1077 flex_dont_budge MOV     R0,#0                   ;Refuse the budge
1078                 MOVS    PC,R14                  ;And return
1079
1080         ]
1081
1082 ; --- flex_die / flex__exit ---
1083 ;
1084 ; On entry:     --
1085 ;
1086 ; On exit:      --
1087 ;
1088 ; Use:          Kills the dynamic area which we own.
1089
1090         [ OPT_DYNAREA
1091
1092         [ OPT_SAPPHIRE
1093 flex__exit      ROUT
1094         |
1095                 EXPORT  flex_die
1096 flex_die        ROUT
1097         ]
1098
1099
1100                 STMFD   R13!,{R0,R1,R14}        ;Save some registers
1101
1102                 ; --- The C library's `atexit' doesn't provide context ---
1103
1104         [ :LNOT:OPT_SAPPHIRE
1105                 WSPACE  flex__wSpace
1106         ]
1107
1108                 ; --- Now free the dynamic area ---
1109
1110                 LDR     R1,flex__dynArea        ;Load the handle
1111                 CMP     R1,#0                   ;Is it defined?
1112                 MOVNE   R0,#1                   ;Yes -- remove it
1113                 SWINE   OS_DynamicArea          ;Do the remove job
1114                 MOVNE   R0,#0                   ;Now clear the handle
1115                 STRNE   R0,flex__dynArea        ;So we don't do it again
1116                 LDMFD   R13!,{R0,R1,PC}^        ;Finally, return to caller
1117
1118                 LTORG
1119
1120         ]
1121
1122         [ OPT_STACK
1123
1124 ; --- flex_stackPtr ---
1125 ;
1126 ; On entry:     R0 == 0 to read, or value to set
1127 ;
1128 ; On exit:      R0 == old value
1129 ;
1130 ; Use:          Either reads or writes the flex stack pointer.  This sort
1131 ;               of thing is useful in exception handlers etc.
1132
1133                 EXPORT  flex_stackPtr
1134 flex_stackPtr   ROUT
1135
1136                 STMFD   R13!,{R12,R14}          ;Save some registers
1137                 WSPACE  flex__wSpace            ;Find the workspace
1138                 LDR     R14,flex__relocSP       ;Load the current value
1139                 CMP     R0,#0                   ;Does he want to write it?
1140                 STRNE   R0,flex__relocSP        ;Yes -- then write it
1141                 MOV     R0,R14                  ;Return the old value
1142                 LDMFD   R13!,{R12,PC}^          ;And return to caller
1143
1144                 LTORG
1145
1146 ; --- flex_save ---
1147 ;
1148 ; On entry:     R0 == value to save, for APCS
1149 ;
1150 ; On exit:      --
1151 ;
1152 ; Use:          Saves some registers on the flex relocation stack.  R13
1153 ;               and R14 cannot be saved -- these registers are corrupted
1154 ;               during this routine's execution.
1155 ;
1156 ;               Values saved on the flex relocation stack are adjusted as
1157 ;               flex moves blocks of memory around, so that they still point
1158 ;               to the same thing as they did before.  Obviously, values
1159 ;               which aren't pointers into flex blocks may be corrupted.
1160 ;               Values pointing to objects deleted (either free blocks, or
1161 ;               areas removed by flex_midExtend) may also be corrupted.
1162 ;
1163 ;               Since this routine takes no arguments, some other method has
1164 ;               to be used.  The method chosen is to follow the call to
1165 ;               flex_save with a LDM or STM instruction containing the
1166 ;               registers to be saved.  This instruction is skipped by the
1167 ;               routine, and thus not executed.
1168 ;
1169 ;               Note that if you give the LDM or STM the same condition code
1170 ;               as the BL preceding it, it will never be executed, since
1171 ;               flex_save skips it if the condition is true and it can't be
1172 ;               executed if the condition is false.
1173 ;
1174 ;               (All the above is only true for the Sapphire version.)
1175
1176                 EXPORT  flex_save
1177 flex_save       ROUT
1178
1179         [ :LNOT:OPT_APCS
1180
1181                 ; --- StrongARM friendly version 1st October 1996 [mdw] ---
1182
1183                 STMFD   R13!,{R10,R11,R12,R14}  ;Save some registers away
1184                 BIC     R10,R14,#&FC000003      ;Clear processor flags
1185                 WSPACE  flex__wSpace            ;Locate flex's workspace
1186                 LDR     R11,flex__relocSP       ;Load the stack pointer
1187                 LDR     R10,[R10,#0]            ;Load the instruction out
1188
1189                 ; --- Rather optimised code ---
1190                 ;
1191                 ; Shift two bits at a time into C and N.  Leave early if
1192                 ; possible.
1193
1194                 TST     R10,#&03F
1195                 BEQ     %f05
1196                 MOVS    R14,R10,LSL #31
1197                 STRMI   R0,[R11],#4
1198                 STRCS   R1,[R11],#4
1199                 MOVS    R14,R10,LSL #29
1200                 STRMI   R2,[R11],#4
1201                 STRCS   R3,[R11],#4
1202                 TST     R10,#&FF0
1203                 BEQ     %f05
1204                 MOVS    R14,R10,LSL #27
1205                 STRMI   R4,[R11],#4
1206                 STRCS   R5,[R11],#4
1207                 TST     R10,#&FC0
1208                 BEQ     %f00
1209 05              MOVS    R14,R10,LSL #25
1210                 STRMI   R6,[R11],#4
1211                 STRCS   R7,[R11],#4
1212                 MOVS    R14,R10,LSL #23
1213                 STRMI   R8,[R11],#4
1214                 STRCS   R9,[R11],#4
1215                 TST     R10,#&C00
1216                 BEQ     %f00
1217                 MOVS    R14,R10,LSL #21
1218                 LDRMI   R14,[R13,#0]
1219                 STRMI   R14,[R11],#4
1220                 LDRCS   R14,[R13,#4]
1221                 STRCS   R14,[R11],#4
1222 00
1223                 ; --- Tidy up and return home ---
1224
1225                 STR     R11,flex__relocSP       ;Store new stack ptr
1226                 LDMFD   R13!,{R10,R11,R12,R14}  ;And return to caller
1227                 ADDS    PC,R14,#4
1228
1229         |
1230
1231                 STMFD   R13!,{R12,R14}          ;Save registers
1232                 WSPACE  flex__wSpace            ;Find my workspace
1233                 LDR     R14,flex__relocSP       ;Load the current pointer
1234                 STR     R0,[R14],#4             ;Store the value away
1235                 STR     R14,flex__relocSP       ;Store the stack pointer
1236                 LDMFD   R13!,{R12,PC}^          ;And return to caller
1237
1238         ]
1239
1240                 LTORG
1241
1242 ; --- flex_load ---
1243 ;
1244 ; On entry:     --
1245 ;
1246 ; On exit:      Registers loaded from relocation stack as requested
1247 ;
1248 ; Use:          Restores registers saved on flex's relocation stack.  See
1249 ;               flex_save for calling information and details about the
1250 ;               relocation stack.
1251
1252                 EXPORT  flex_load
1253 flex_load       ROUT
1254
1255         [ :LNOT:OPT_APCS
1256
1257                 ; --- StrongARM friendly version 1st October 1996 [mdw] ---
1258
1259                 STMFD   R13!,{R10,R11,R12,R14}  ;Save some registers away
1260                 BIC     R10,R14,#&FC000003      ;Clear processor flags
1261                 WSPACE  flex__wSpace            ;Locate flex's workspace
1262                 LDR     R11,flex__relocSP       ;Load the stack pointer
1263                 LDR     R10,[R10,#0]            ;Load the instruction out
1264
1265                 ; --- Rather optimised code ---
1266                 ;
1267                 ; Shift two bits at a time into C and N.  Leave early if
1268                 ; possible.  Do it backwards, because otherwise it doesn't
1269                 ; work.
1270
1271                 TST     R10,#&FF0
1272                 BEQ     %f05
1273                 MOVS    R14,R10,LSL #21
1274                 LDRCS   R14,[R11,#-4]!
1275                 STRCS   R14,[R13,#4]
1276                 LDRMI   R14,[R11,#-4]!
1277                 STRMI   R14,[R13,#0]
1278                 MOVS    R14,R10,LSL #23
1279                 LDRCS   R9,[R11,#-4]!
1280                 LDRMI   R8,[R11,#-4]!
1281                 TST     R10,#&0FF
1282                 BEQ     %f00
1283                 MOVS    R14,R10,LSL #25
1284                 LDRCS   R7,[R11,#-4]!
1285                 LDRMI   R6,[R11,#-4]!
1286                 TST     R10,#&03F
1287                 BEQ     %f00
1288                 MOVS    R14,R10,LSL #27
1289                 LDRCS   R5,[R11,#-4]!
1290                 LDRMI   R4,[R11,#-4]!
1291                 TST     R10,#&00F
1292                 BEQ     %f00
1293 05              MOVS    R14,R10,LSL #29
1294                 LDRCS   R3,[R11,#-4]!
1295                 LDRMI   R2,[R11,#-4]!
1296                 MOVS    R14,R10,LSL #31
1297                 LDRCS   R1,[R11,#-4]!
1298                 LDRMI   R0,[R11,#-4]!
1299 00
1300                 ; --- Tidy up and return home ---
1301
1302                 STR     R11,flex__relocSP       ;Store new stack ptr
1303                 LDMFD   R13!,{R10,R11,R12,R14}  ;And return to caller
1304                 ADDS    PC,R14,#4
1305
1306         |
1307
1308                 STMFD   R13!,{R12,R14}          ;Save registers
1309                 WSPACE  flex__wSpace            ;Find my workspace
1310                 LDR     R14,flex__relocSP       ;Load the current pointer
1311                 LDR     R0,[R14,#-4]!           ;Load the value out
1312                 STR     R14,flex__relocSP       ;Store the stack pointer
1313                 LDMFD   R13!,{R12,PC}^          ;And return to caller
1314
1315         ]
1316
1317                 LTORG
1318
1319 ; --- flex__reloc ---
1320 ;
1321 ; On entry:     R0 == destination pointer of move
1322 ;               R1 == source pointer of move
1323 ;               R2 == length of block to move
1324 ;
1325 ; On exit:      --
1326 ;
1327 ; Use:          Relocates the flex stack after a heap operation which moved
1328 ;               memory.  The arguments are intentionally the same as those
1329 ;               for fastMove, which should be called immediately before this
1330 ;               routine.
1331
1332 flex__reloc     ROUT
1333
1334                 STMFD   R13!,{R3,R4,R14}        ;Save some registers
1335
1336                 ; --- Set up initial values ---
1337
1338                 ADR     R3,flex__relocStk       ;Point to the flex stack base
1339                 LDR     R4,flex__relocSP        ;Load the current stack ptr
1340
1341                 ; --- Go through all the stack entries ---
1342
1343 00flex__reloc   CMP     R3,R4                   ;Have we reached the end?
1344                 LDMGEFD R13!,{R3,R4,PC}^        ;Yes -- return to caller
1345                 LDR     R14,[R3],#4             ;Load the saved value
1346                 SUB     R14,R14,R1              ;Subtract the source base
1347                 CMP     R14,R2                  ;Is value within block?
1348                 ADDLO   R14,R14,R0              ;Yes -- add the destination
1349                 STRLO   R14,[R3,#-4]            ;Store pointer if it changed
1350                 B       %00flex__reloc          ;And go round for the rest
1351
1352                 LTORG
1353
1354         ]
1355
1356 ; --- flex_dump ---
1357
1358         [ OPT_DUMP
1359
1360                 EXPORT  flex_dump
1361 flex_dump       ROUT
1362
1363                 STMFD   R13!,{R0-R12,R14}
1364                 SWI     XOS_NewLine
1365                 SWI     XOS_NewLine
1366                 SWI     XOS_Write0
1367                 SWI     XOS_NewLine
1368
1369                 LDR     R11,=flex__data
1370                 LDR     R5,[R11,#flex__base]
1371                 LDR     R6,[R11,#flex__free]
1372                 LDR     R7,[R11,#flex__end]
1373
1374                 SWI     XOS_WriteS
1375                 DCB     "Heap base: ",0
1376                 MOV     R0,R5
1377                 BL      writeHex
1378                 SWI     XOS_WriteS
1379                 DCB     13,10,"Heap free area: ",0
1380                 MOV     R0,R6
1381                 BL      writeHex
1382                 SWI     XOS_WriteS
1383                 DCB     13,10,"Heap end: ",0
1384                 MOV     R0,R7
1385                 BL      writeHex
1386
1387 00              CMP     R5,R6
1388                 LDMGEFD R13!,{R0-R12,PC}^
1389
1390                 SWI     XOS_WriteS
1391                 DCB     13,10,10,"Block address: ",0
1392                 MOV     R0,R5
1393                 BL      writeHex
1394                 SWI     XOS_WriteS
1395                 DCB     13,10,"  Size: ",0
1396                 LDR     R0,[R5,#flex__size]
1397                 BL      writeHex
1398                 SWI     XOS_WriteS
1399                 DCB     13,10,"  Anchor: ",0
1400                 LDR     R0,[R5,#flex__bkanchor]
1401                 BL      writeHex
1402                 LDR     R0,[R5,#flex__size]
1403                 ADD     R0,R0,#flex__ohead+7
1404                 BIC     R0,R0,#7
1405                 ADD     R5,R5,R0
1406                 B       %00
1407
1408 writeHex        STMFD   R13!,{R1,R2,R14}
1409                 SUB     R1,R13,#256
1410                 MOV     R2,#256
1411                 SWI     XOS_ConvertHex8
1412                 SWI     XOS_Write0
1413                 LDMFD   R13!,{R1,R2,PC}^
1414
1415 writeDec        STMFD   R13!,{R1,R2,R14}
1416                 SUB     R1,R13,#256
1417                 MOV     R2,#256
1418                 SWI     XOS_ConvertInteger4
1419                 SWI     XOS_Write0
1420                 LDMFD   R13!,{R1,R2,PC}^
1421
1422                 LTORG
1423
1424         ]
1425
1426 ;----- Workspace ------------------------------------------------------------
1427
1428 ; --- Flags ---
1429
1430 fFlag__inited   EQU     (1<<0)                  ;We are currently running
1431 fFlag__compact  EQU     (1<<1)                  ;The heap is compact ATM
1432
1433         [ OPT_DYNAREA
1434 fFlag__dynArea  EQU     (1<<2)                  ;Using a dynamic area
1435         ]
1436
1437 ; --- Flex block format ---
1438
1439                 ^       0
1440 flex__bkanchor  #       4                       ;Back-pointer to flex anchor
1441 flex__size      #       4                       ;Size of this flex block
1442 flex__ohead     #       0                       ;The flex overhead on blocks
1443
1444 ; --- Static data ---
1445
1446         [ :LNOT:OPT_STANDALONE
1447
1448                 ^       0,R12
1449 flex__wStart    #       0
1450
1451         [ OPT_DYNAREA
1452                 GBLL    FLEXWS_DYNAREA
1453         ]
1454
1455         [ OPT_STACK
1456                 GBLL    FLEXWS_STACK
1457         ]
1458
1459                 GET     libs:sh.flexws
1460
1461 flex__wSize     EQU     {VAR}-flex__wStart
1462
1463         ]
1464
1465         [ OPT_SAPPHIRE
1466                 AREA    |Sapphire$$LibData|,CODE,READONLY
1467                 DCD     flex__wSize
1468                 DCD     flex__wSpace
1469                 DCD     0
1470                 DCD     flex_init
1471         ]
1472
1473         [ OPT_APCS
1474                 AREA    |C$$zidata|,DATA,NOINIT
1475 flex__sSpace    %       flex__wSize
1476         ]
1477
1478 ;----- That's all, folks ----------------------------------------------------
1479
1480                 END