; Copyright 1996 Acorn Computers Ltd
;
; Licensed under the Apache License, Version 2.0 (the "License");
; you may not use this file except in compliance with the License.
; You may obtain a copy of the License at
;
;     http://www.apache.org/licenses/LICENSE-2.0
;
; Unless required by applicable law or agreed to in writing, software
; distributed under the License is distributed on an "AS IS" BASIS,
; WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied.
; See the License for the specific language governing permissions and
; limitations under the License.
;
        TTL   => ChangeDyn

;******************************************************************************
; ChangeDynamic SWI
; In  : R0 =  0 => System Heap,
;             1 => RMA
;             2 => Screen
;             3 => Sprite area
;             4 => Font cache
;             5 => RAM disc
;             6 => Free pool
;       R1 = no of bytes to change by
;
; Out : V set if CAO in AplWork or couldn't move all the bytes requested.
;       R1 set to bytes moved.
;******************************************************************************

; The following flag controls the operation of ReadCMOSAndConfigure and FudgeConfigureRMA
;
; If false, then no memory is in the free pool to start off, and these routines just allocate pages
; starting at page R2, and update this on exit.
;
; If true, then routine InitDynamicAreas initially moves all non-static free memory into the free pool,
; and then the above routines just take pages off the end of that.

        GBLL    GetPagesFromFreePool    ; whether ReadCMOSAndConfigure extract pages from the free pool
GetPagesFromFreePool SETL NewCDA :LAND: {TRUE}

 [ ExpandedCamMap
AP_AppSpace     *       0                                       ; user r/w, CB
AP_SysHeap      *       0                                       ; user r/w, CB
AP_RMA          *       0                                       ; user r/w, CB
  [ NewStyle_Screen
   [ DAF_SpecifyBit
AP_Screen       *       0 :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_DoublyMapped :OR: DynAreaFlags_NeedsSpecificPages
   |
AP_Screen       *       0 :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_DoublyMapped
   ]
  |
AP_Screen       *       0 :OR: DynAreaFlags_NotCacheable        ; user r/w, ~CB
  ]
AP_Sprites      *       0                                       ; user r/w, CB
AP_FontArea     *       2                                       ; user none, CB
AP_RAMDisc      *       2 :OR: DynAreaFlags_NotCacheable        ; user none, ~CB
AP_Duff         *       2 :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_NotBufferable ; user none, ~C~B
  [ UseFreePool
AP_FreePool     *       2 :OR: DynAreaFlags_NotCacheable        ; user none, ~CB
  ]
AP_CursorChunk  *       1 :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_NotBufferable :OR: PageFlags_Unavailable
AP_PageZero     *       0
  [ MEMM_Type = "ARM600"
AP_L2PT         *       2 :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_NotBufferable ; user none, ~C~B
AP_L1PT         *       AP_L2PT :OR: PageFlags_Unavailable
AP_UndStackSoftCam *    PageFlags_Unavailable
  ]
 |
AP_AppSpace     *       0                                       ; user r/w
AP_SysHeap      *       0                                       ; user r/w
AP_RMA          *       0                                       ; user r/w
AP_Screen       *       0                                       ; user r/w
AP_Sprites      *       0                                       ; user r/w
AP_FontArea     *       2                                       ; user none
AP_RAMDisc      *       2                                       ; user none
AP_Duff         *       2
  [ UseFreePool
AP_FreePool     *       2                                       ; user none
  ]
AP_CursorChunk  *       1                                       ; user r-o
AP_PageZero     *       0                                       ; user r/w
 ]

ChangeDyn_FreeAndApl * -2               ; special reason code for when we're sucking out of free pool and apl space
ChangeDyn_AplSpace   * -1
ChangeDyn_SysHeap    * 0
ChangeDyn_RMA        * 1
ChangeDyn_Screen     * 2
ChangeDyn_SpriteArea * 3
ChangeDyn_FontArea   * 4
ChangeDyn_RamFS      * 5
ChangeDyn_FreePool   * 6
 [ UseFreePool
ChangeDyn_MaxArea    * 6
 |
ChangeDyn_MaxArea    * 5
 ]

; Area handler reason codes

DAHandler_PreGrow       *       0
DAHandler_PostGrow      *       1
DAHandler_PreShrink     *       2
DAHandler_PostShrink    *       3

; Number of entries in page block on stack

NumPageBlockEntries *   32
PageBlockSize   *       NumPageBlockEntries * 12
PageBlockChunk  *       NumPageBlockEntries * 4096

        InsertDebugRoutines

; *** Start of old style code ***

 [ :LNOT: NewStyle_All

ChangeDynamicSWI ROUT
        Push    "r0, r2-r9, r10, lr"        ; r10 is workspace

  [ NewCDA2
        B       CheckForNewArea
IsOldArea
  ]

        CMP     r0, #ChangeDyn_MaxArea
        MOVLS   r10, #0
        LDRLS   r10, [r10, #IRQsema]
        CMPLS   r10, #0
        BHI     failure_IRQgoing

 [ DebugCDA
        DLINE   "Entering OS_ChangeDynamicArea"
        DREG    r0, "r0 = "
        DREG    r1, "r1 = "
 ]

 [ :LNOT: NewStyle_RAMDisc
        CMP     r0, #ChangeDyn_RamFS
        BEQ     CheckRAMFSChangeOK
AllowRAMFSChange
 ]

        MOV     r6, #0
        LDR     r6, [r6, #Page_Size]
        SUB     r12, r6, #1
        ADD     r1, r1, r12
        BICS    r1, r1, r12                     ; round up to nearest page.
        MOVEQ   r11, r0                         ; area
        MOVEQ   r10, #0                         ; amount moved
        BEQ     CDS_PostService                 ; zero pages!

; Now form source (r11) and destination (r12) registers

 [ UseFreePool

        CMP     r0, #ChangeDyn_FreePool         ; if specified area is free pool
        MOVEQ   r11, #ChangeDyn_AplSpace        ; then "other" area is aplspace
        MOVNE   r11, #ChangeDyn_FreePool        ; else other area is free pool

        CMP     r1, #0                          ; if growing area
        MOVPL   r12, r0                         ; then dest is specified area, and src is other
        MOVMI   r12, r11                        ; else dest is other
        MOVMI   r11, r0                         ; and src is specified
        RSBMI   r1, r1, #0                      ; and make change positive
 |
        MOVMI   r12, #ChangeDyn_AplSpace        ; dest := ApplWork
        MOVMI   r11, r0                         ; source := R0
        MOVPL   r12, r0                         ; dest := R0
        MOVPL   r11, #ChangeDyn_AplSpace        ; source := ApplWork
        RSBMI   r1, r1, #0
 ]

 [ DebugCDA
        DREG    r11, "Initially, src = "
        DREG    r12, "and dest = "
 ]

; amount movable = current size(source) - shrink limit(source)

 [ :LNOT: NewStyle_SpriteArea
        CMP     r11, #ChangeDyn_SpriteArea
        LDREQ   r10, [r11, #SpriteSize-ChangeDyn_SpriteArea]
        TEQEQ   r10, #0                 ; May have no sprite area ...
        MOVEQ   r5, #0                  ; Shrink limit := 0
        BEQ     gotsizeandshrink
 ]

; need to lock the heap if we are shrinking the SysHeap or the RMA
; lock by setting the heap end to be the same as the current base;
; this ensures that no claims will use memory about to disappear

        ADRL    r10, Current_Size+4
        LDR     r10, [r10, r11, LSL #2]                 ; get pointer to current size of area

 [ NewStyle_RMA :LAND: NewStyle_SysHeap                 ; if both new
        LDR     r10, [r10]                              ; then just get current size
 |
  [ NewStyle_SysHeap                                    ; if sys heap new
        CMP     r11, #ChangeDyn_RMA                     ; then RMA must be old
  |
        CMP     r11, #ChangeDyn_SysHeap                 ; else sys heap is old
   [ :LNOT: NewStyle_RMA
        CMPNE   r11, #ChangeDyn_RMA                     ; and if RMA old as well, do 2 CMPs
   ]
  ]
        LDRNE   r10, [r10]
        BNE     CDA_GotSize

; its a heap, so munge it to prevent anyone stealing memory while we are

        MOV     lr, pc                                  ; save I_bit
        TEQP    pc, #SVC_mode + I_bit                   ; disable IRQs round this bit
        LDR     r5, [r10]                               ; current size
        LDR     r2, [r10, #hpdbase-hpdend]              ; remove all of the contiguous free chunk from the heap
        STR     r2, [r10]                               ; so that noone can steal any of it under IRQs
        MOV     r10, r5
        STR     r10, [stack, #4*9]                      ; but save the old size on stack to restore later
        TEQP    lr, #0                                  ; restore state

CDA_GotSize
 ]
 [ :LNOT: NewStyle_FontArea
        CMP     r11, #ChangeDyn_FontArea
        BNE     %FT04                                   ; source not font area

        MOV     r5, r1
        MOV     r1, #-1
        MOV     r2, #0                                  ; in case font manager dead
        SWI     XFont_ChangeArea
        MOV     r1, r5                                  ; preserve r1
        MOV     r5, r2
        B       %FT05
04
 ]
        ADR     r5, Shrink_Limits+4                     ; now see how much we can remove from src
        LDR     r5, [r5, r11, LSL #2]                   ; load shrink limit address
        LDR     r5, [r5]                                ; and contents
05
 [ :LNOT: NewStyle_SpriteArea
        CMP     r11, #ChangeDyn_SpriteArea
        CMPEQ   r5, #saExten                            ; if no sprites defined, can delete hdr
        MOVEQ   r5, #0
 ]

gotsizeandshrink
        SUB     r10, r10, r5                            ; amount removable from source
06
        ADR     r5, Grow_LimitsPtrs+4
        LDR     r5, [r5, r12, LSL #2]                   ; get ptr to maximum size of destination area
        LDR     r5, [r5]                                ; maximum size of dest area

 [ MEMC_Type = "IOMD"
        CMP     r12, #ChangeDyn_Screen                  ; if screen
        MOVEQ   r5, #0
        LDREQ   r5, [r5, #VideoSize]                    ; then maximum size depends on how much video RAM there is
 ]

        ADRL    r4, Current_Size+4
        LDR     r4, [r4, r12, LSL #2]                   ; pointer to destination current size
        LDR     r4, [r4]                                ; current size of dest
        SUB     r5, r5, r4                              ; maximum amount we can add to destination

; r10 = amount removable from src, r5 = amount addable to dest

        MOV     r2, r10                                 ; save amount removable from src, in case we need it again
        CMP     r10, r5
        MOVHI   r10, r5                                 ; min(max removable from src, max addable to dest)

; r10 is now the amount we can move
;  IF removing from ApplWork AND amount moveable < size requested
;    Then Error NotAllMoved

        CMP     r10, r1
        BCS     %FT10                                   ; can move all reqd (TMD 15-Oct-91; was GE)

; we can't move all that is required - there are two cases to be considered
;  a) if (src = AplSpace) and (dest <> FreePool) then give error (this can only happen in old world)
;  b) if (src = FreePool) AND (dest <> AplSpace) then check if adding aplspace would allow us to succeed -
;        if it does then adjust registers, else give error

        CMP     r11, #ChangeDyn_AplSpace                ; if src = aplspace
        BNE     %FT08                                   ; [not, so skip]
        CMP     r12, #ChangeDyn_FreePool                ; and dest <> freepool
        BNE     failure_IRQgoing                         ; then fail (case (a))
08
 [ UseFreePool
        CMP     r11, #ChangeDyn_FreePool                ; if src = FreePool
        BNE     %FT10                                   ; [skip if not]
        CMP     r12, #ChangeDyn_AplSpace                ; and dest <> AplSpace
        BEQ     %FT10                                   ; [skip if not]

; now see if we would have enough if we had aplspace as well (r2 = amount we could remove from free pool)

  [ DebugCDA
        DLINE   "Not enough in just free pool"
  ]

        LDR     r4, Current_Size+4+(ChangeDyn_AplSpace :SHL: 2)
        LDR     r4, [r4]                                ; r4 = current apl size
        LDR     lr, Shrink_Limits+4+(ChangeDyn_AplSpace :SHL: 2)
        LDR     lr, [lr]                                ; lr = shrink limit for aplspace
        SUB     r4, r4, lr                              ; r4 = amount we could remove from aplspace

        ADD     r10, r2, r4                             ; add on to amount we could remove from free pool
        CMP     r10, r5                                 ; if more than amount area can grow
        MOVHI   r10, r5                                 ; then limit to that

        CMP     r10, r1                                 ; if still can't do it now
        BCC     failure_IRQgoing                         ; then give error

        TEQ     r2, #0                                  ; else check to see if there was any at all in free pool
        MOVEQ   r11, #ChangeDyn_AplSpace                ; if not then just take from aplspace
        MOVEQ   r5, r10                                 ; and do all

        MOVNE   r11, #ChangeDyn_FreeAndApl              ; else make src indicator reflect that we need both
        MOVNE   r5, r2                                  ; but save amount we are taking from freepool
        B       %FT10
 ]

 [ (:LNOT: NewStyle_SysHeap) :LOR: (:LNOT: NewStyle_RMA)
testrestoreheapend
  [ NewStyle_SysHeap                                    ; if sys heap new
        CMP     r11, #ChangeDyn_RMA                     ; then RMA must be old
  |
        CMP     r11, #ChangeDyn_SysHeap                 ; else sys heap is old
   [ :LNOT: NewStyle_RMA
        CMPNE   r11, #ChangeDyn_RMA                     ; and if RMA old as well, do 2 CMPs
   ]
  ]
        LDREQ   r2, [stack, #4*9]
        ADREQL  r3, Current_Size + 4
        LDREQ   r3, [r3, r11, LSL #2]
        STREQ   r2, [r3]
        MOV     pc, lr
 ]

UserMemStartAddr & UserMemStart

Shrink_Limits                                   ; locations to look at
        &       UserMemStartAddr                ; AplWork - unfudged
 [ NewStyle_SysHeap
        &       &FE000000                       ; cause abort
 |
        &       SysHeapStart + :INDEX: hpdbase  ; SysHeap
 ]
 [ NewStyle_RMA
        &       &FE000000                       ; cause abort
 |
        &       RMAAddress + :INDEX: hpdbase    ; RMA
 ]
        &       VduDriverWorkSpace + ScreenSize ; Screen
 [ NewStyle_SpriteArea
        &       &FE000000                       ; cause abort
 |
        &       SpriteSpaceAddress + saFree     ; Sprites
 ]
 [ NewStyle_FontArea
        &       &FE000000                       ; cause abort
 |
        &       0                               ; Fonts not needed
 ]
 [ NewStyle_RAMDisc
        &       &FE000000                       ; cause abort
 |
        &       MinRamFSSize                    ; RAMFS
 ]
        &       MinFreePoolSize                 ; Free pool

 [ :LNOT: NewStyle_RAMDisc
MinRamFSSize
 ]
MinFreePoolSize
        &       0



Grow_LimitsPtrs
 [ NewCDA
        &       AppSpaceDANode + DANode_MaxSize ; AplWork
 |
        &       AppSpaceMaxSizePtr
 ]
 [ NewStyle_SysHeap
        &       &FE000000                       ; cause abort
 |
        &       SysHeapMaxSizePtr               ; SysHeap
 ]
 [ NewStyle_RMA
        &       &FE000000                       ; cause abort
 |
        &       RMAMaxSizePtr                   ; RMA
 ]
        &       ScreenMaxSizePtr                ; Screen
 [ NewStyle_SpriteArea
        &       &FE000000                       ; cause abort
 |
        &       SpriteSpaceMaxSizePtr           ; Sprites
 ]
 [ NewStyle_FontArea
        &       &FE000000                       ; cause abort
 |
        &       FontCacheMaxSizePtr             ; Fonts
 ]
 [ NewStyle_RAMDisc
        &       &FE000000                       ; cause abort
 |
        &       RAMDiscMaxSizePtr               ; RAMFS
 ]
 [ UseFreePool
        &       FreePoolDANode + DANode_MaxSize ; Free pool
 ]

; The following will eventually become redundant as more and more areas become new ones
; Ultimately the whole lot can be removed when no old areas exist (perhaps in my grandson's lifetime!)

 [ :LNOT: NewStyle_SysHeap
SysHeapMaxSizePtr       &       SysHeapMaxSize
 ]
 [ :LNOT: NewStyle_RMA
RMAMaxSizePtr           &       RMAMaxSize
 ]
ScreenMaxSizePtr        &       ScreenMaxSize
 [ :LNOT: NewStyle_SpriteArea
SpriteSpaceMaxSizePtr   &       SpriteSpaceMaxSize
 ]
 [ :LNOT: NewStyle_FontArea
FontCacheMaxSizePtr     &       FontCacheMaxSize
 ]
 [ :LNOT: NewStyle_RAMDisc
RAMDiscMaxSizePtr       &       RAMDiscMaxSize
 ]
 [ :LNOT: NewCDA
AppSpaceMaxSizePtr      &       AplWorkMaxSize
 ]


Access_Rights
        &       AP_AppSpace
        &       AP_SysHeap
        &       AP_RMA
        &       AP_Screen
        &       AP_Sprites
        &       AP_FontArea
        &       AP_RAMDisc
 [ UseFreePool
        &       AP_FreePool
 ]

10
        CMP     r10, r1                         ; if can move more than asked for
        MOVHI   r10, r1                         ; then move requested amount (TMD 15-Oct-91; was GT)
        BCS     %FT15                           ; (TMD 15-Oct-91); was GE)

; moving less than asked for: set up an error for exit
        ADR     r0, ErrorBlock_ChDynamNotAllMoved
        STR     r0, [stack]
        LDR     r0, [stack, #4*10]
        ORR     r0, r0, #V_bit
        STR     r0, [stack, #4*10]
        SUB     r0, r6, #1                      ; and make amount moveable
        BICS    r10, r10, r0                    ; a pagesize multiple
        BEQ     CDS_PostServiceWithRestore

; IF CAO in ApplWork AND UpCall not claimed THEN Error ChDynamCAO

15
 [ UseFreePool
        MOV     r1, #0                          ; default value if apl space not involved
        CMP     r11, #ChangeDyn_AplSpace        ; if source = aplspace
        RSBEQ   r1, r10, #0                     ; then make amount -ve
        CMP     r11, #ChangeDyn_FreeAndApl      ; if source = free and apl
        SUBEQ   r1, r5, r10                     ; then make it -(amount removing from apl space)
        MOVNE   r5, r10                         ; else set up r5 to be total amount (wasn't set up above)
        CMP     r12, #ChangeDyn_AplSpace        ; if dest = aplspace
        MOVEQ   r1, r10                         ; then make amount +ve

        TEQ     r1, #0                          ; if none of the above
        BEQ     %FT25                           ; then skip this
 |
        MOV     r5, r10                         ; r5 = total amount moving (since no split removes)
        CMP     r11, #ChangeDyn_AplSpace        ; old code - if src = apl
        RSBEQ   r1, r10, #0                     ; then -ve
        MOVNE   r1, r10                         ; else +ve
 ]

 [ DebugCDA
        DREG    r11, "After checking, src = "
        DREG    r12, "and dest = "
        DREG    r10, "Amount moving (total) = "
        DREG    r5,  "Amount moving (partial) = "

        DLINE   "Consulting application about change"
 ]

        MOV     r2, #0
        LDR     r3, [r2, #AplWorkSize]
        LDR     r2, [r2, #Curr_Active_Object]
        CMP     r2, r3                          ; check if CAO outside application space
        BHI     %FT20                           ; [it is so issue Service not UpCall]

; CAO in application space, so issue UpCall to check it's OK

        MOV     r0, #UpCall_MovingMemory :AND: &FF
        ORR     r0, r0, #UpCall_MovingMemory :AND: &FFFFFF00
        TEQ     r1, #0
        RSBMI   r1, r1, #0                      ; r1 passed in is always +ve (probably a bug, but should be compat.)

        SWI     XOS_UpCall                      ; r1 already set up above
        CMP     r0, #UpCall_Claimed
        BEQ     %FT25

        ADRL    r0, ErrorBlock_ChDynamCAO
        B       ChangeDynamic_Error

; IF service call claimed Then Error AplWSpaceInUse

20
        MOV     r0, r1                          ; amount removing from aplspace
        MOV     r1, #Service_Memory
        BL      Issue_Service
        CMP     r1, #Service_Serviced
        BNE     %FT25

        ADRL    r0, ErrorBlock_AplWSpaceInUse
        B       ChangeDynamic_Error

; Right! r10 is amount of memory we will move
; (if moving from free pool + apl space then r5 is amount removing from free pool)
; r11 is the source
; r12 is the destination

25
 [ DebugCDA
        DLINE   "Change is going ahead"
 ]
 [ :LNOT: NewStyle_FontArea
        CMP     r11, #ChangeDyn_FontArea
        LDREQ   r1, [r11, #FontCacheSize-ChangeDyn_FontArea]
        SUBEQ   r1, r1, r10                     ; new size
        SWIEQ   XFont_ChangeArea
 ]

; remove the cursors if screen moving: might flash during modechange wrch

        CMP     r11, #ChangeDyn_Screen
        CMPNE   r12, #ChangeDyn_Screen
        SWIEQ   XOS_RemoveCursors

        CMP     r11, #ChangeDyn_Screen
        RSBEQ   r0, r10, #0

        MOV     r9, pc
        TEQEQP  pc, #SVC_mode+I_bit+Z_bit
        NOP
    ; disable interrupts while sorting out the screen, in case (e.g) screen
    ; start address is being reprogrammed under interrupt

        BLEQ    RemovePages

        TEQP    pc, r9          ; restore interrupt state

; calculate addresses of blocks

        MOV     r9, #0
        LDR     r9, [r9, #MEMC_CR_SoftCopy]

        MOV     r3, r11
        BL      GetBlockEndSource
        MOV     r0, r3                  ; R0 := blockend(source)

        CMP     r12, #ChangeDyn_Screen
        BEQ     ExtendScreen            ; dest=screen: perversion needed

        MOV     r3, r12
        BL      GetBlockEnd             ; R3 := blockend(dest)

; move memory: r5 bytes from r0 backwards to r3 forwards
        MOV     r1, #0
30
        SUB     r0, r0, r6
        Push    "r5,r11"
        ADR     r11, Access_Rights+4
        LDR     r11, [r11, r12, LSL #2] ; get access privs (+ CB bits in new world)
 [ DebugCDA
        DREG    r0, "Moving page at ", cc
        DREG    r3, " to ", cc
        DREG    r11, " with PPL "
 ]
        BL      MoveCAMatR0toR3
        Pull    "r5,r11"
        BVS     cambust
        ADD     r1, r1, r6
        ADD     r3, r3, r6

        CMP     r1, r5                  ; have we done all (of this lot at least)?
        BNE     %BT30                   ; [no, so loop]

        CMP     r5, r10                 ; have we done all of both lots?
        BEQ     %FT33                   ; yes, so finished

        Push    "r1,r3"
        MOV     r3, #ChangeDyn_AplSpace ; else we have more to do, from aplspace
        BL      GetBlockEnd             ; so get apl block end
        MOV     r0, r3                  ; and put into src register
        Pull    "r1,r3"
        MOV     r5, r10
        B       %BT30

33
        CMP     r11, #ChangeDyn_Screen
        BNE     %FT40

; source=screen: need to shuffle rest of screen down.

        VDWS    r5
        LDR     r5, [r5, #TotalScreenSize]
        MOV     r3, #ScreenEndAdr
35
        SUB     r0, r0, r6
        SUB     r3, r3, r6
        Push    "r5"
        MOV     r11, #AP_Screen
        BL      MoveCAMatR0toR3
        Pull    "r5"
        BVS     cambust
        SUBS    r5, r5, r6
        BGT     %BT35
        MOV     r11, #ChangeDyn_Screen

40
; now need to restore sizes if we have locked a heap

 [ (:LNOT: NewStyle_SysHeap) :LOR: (:LNOT: NewStyle_RMA)
        BL      testrestoreheapend
 ]

; update object sizes: current size(dest)   +:= r10
;                      current size(source) -:= r10

        MOV     r4, #0                          ; remember for later
        LDR     r4, [r4, #SpriteSize]

        CMP     r11, #ChangeDyn_FreeAndApl
        BNE     %FT41
        LDR     r2, Current_Size+4+(ChangeDyn_FreePool :SHL: 2)         ; r2 -> old size of free pool
        LDR     lr, [r2]                                                ; lr = old size
        LDR     r3, Shrink_Limits+4+(ChangeDyn_FreePool :SHL: 2)        ; r3 -> shrink limit of free pool
        LDR     r3, [r3]                                                ; r3 = shrink limit
        SUB     lr, lr, r3                                              ; how much we took out of it
        STR     r3, [r2]                                                ; put shrink limit into current size

        LDR     r2, Current_Size+4+(ChangeDyn_AplSpace :SHL: 2)         ; r2 -> old size of apl space
        LDR     r3, [r2]                                                ; r3 = old size of apl space
        SUB     r3, r3, r10                                             ; how much we would have taken out of it
        ADD     r3, r3, lr                                              ; but don't take out the stuff which came out of free
        STR     r3, [r2]
        ADR     r0, Current_Size+4
        B       %FT42

41
        ADR     r0, Current_Size+4
        CMP     r11, #ChangeDyn_Screen          ; don't update TotalScreenSize
        LDRNE   r2, [r0, r11, LSL #2]
        LDRNE   r3, [r2]
        SUBNE   r3, r3, r10
        STRNE   r3, [r2]
42
        CMP     r12, #ChangeDyn_Screen          ; don't update TotalScreenSize
        LDRNE   r2, [r0, r12, LSL #2]
        LDRNE   r3, [r2]
        ADDNE   r3, r3, r10
        STRNE   r3, [r2]

 [ :LNOT: NewStyle_SpriteArea
        CMP     r11, #ChangeDyn_SpriteArea      ; watch out for sprite area creation
        CMPNE   r12, #ChangeDyn_SpriteArea      ; or deletion
        BNE     %FT45

        MOV     r1, #0                          ; used later also!!
        LDR     r3, [r1, #SpriteSize]
        CMP     r3, #0                          ; if sprite area deleted
        LDRNE   r3, =SpriteSpaceAddress         ; tell the vdu drivers
        MOV     r14, #VduDriverWorkSpace
        STR     r3, [r14, #SpAreaStart]
        BEQ     %FT45                           ; and don't touch non-existent memory

        CMP     r4, #0                          ; if area was null,
        LDMNEIB r3, {r4-r6}                     ; (skip size)
        MOVEQ   r4, #0                          ; initialise variables if was null
        MOVEQ   r5, #saExten
        MOVEQ   r6, #saExten
        LDR     r0, [r1, #SpriteSize]           ; set up earlier
        STMIA   r3, {r0,r4-r6}                  ; stash new set of variables
45
 ]
 [ UseFreePool
        CMP     r11, #ChangeDyn_AplSpace        ; if apl space involved in transfer
        CMPNE   r11, #ChangeDyn_FreeAndApl
        CMPNE   r12, #ChangeDyn_AplSpace
        MOVEQ   r0, #0
        LDREQ   r2, [r0, #AplWorkSize]          ; then reset memlimit to aplworksize
        STREQ   r2, [r0, #MemLimit]             ; MemLimit := AplWorkSize
 |
        MOV     r0, #0
        LDR     r2, [r0, #AplWorkSize]
        STR     r2, [r0, #MemLimit]             ; MemLimit := AplWorkSize
 ]

        CMP     r12, #ChangeDyn_Screen
        MOVEQ   r0, r10

        MOV     r9, pc
        TEQEQP  pc, #SVC_mode+I_bit+Z_bit
    ; disable interrupts while sorting out the screen, in case (e.g) screen
    ; start address is being reprogrammed under interrupt

        BLEQ    InsertPages

        TEQP    pc, r9       ; restore interrupt state

        CMP     r11, #ChangeDyn_Screen
        CMPNE   r12, #ChangeDyn_Screen
        SWIEQ   XOS_RestoreCursors

 [ :LNOT: NewStyle_FontArea
        CMP     r12, #ChangeDyn_FontArea
        LDREQ   r1, [r12, #FontCacheSize-ChangeDyn_FontArea]
        SWIEQ   XFont_ChangeArea
 ]

 [ :LNOT: NewStyle_RAMDisc
        CMP     r11, #ChangeDyn_RamFS
        CMPNE   r12, #ChangeDyn_RamFS
        BEQ     reinitialise_RAMFS
 ]
        B       CDS_PostService

Current_Size
        &       AplWorkSize                             ; AplWork
 [ NewStyle_SysHeap
        &       &FE000000                               ; cause abort
 |
        &       SysHeapStart + :INDEX: hpdend           ; SysHeap
 ]
 [ NewStyle_RMA
        &       &FE000000                               ; cause abort
 |
        &       RMAAddress + :INDEX: hpdend             ; RMA
 ]
        &       VduDriverWorkSpace + TotalScreenSize    ; Screen
 [ NewStyle_SpriteArea
        &       &FE000000                               ; cause abort
 |
        &       SpriteSize                              ; sprites
 ]
 [ NewStyle_FontArea
        &       &FE000000                               ; cause abort
 |
        &       FontCacheSize                           ; fonts
 ]
 [ NewStyle_RAMDisc
        &       &FE000000                               ; cause abort
 |
        &       RAMDiscSize                             ; RAMFS
 ]
 [ UseFreePool
        &       FreePoolDANode + DANode_Size            ; Free pool
 ]

GetBlockEndSource
        CMP     r3, #ChangeDyn_FreeAndApl               ; if removing from free + apl
        MOVEQ   r3, #ChangeDyn_FreePool                 ; then start by removing from free pool
 [ (:LNOT: NewStyle_RMA) :LOR: (:LNOT: NewStyle_SysHeap) ; none of this needed if both sysheap+RMA new
  [ NewStyle_SysHeap                                    ; if sys heap new
        CMP     r3, #ChangeDyn_RMA                      ; then RMA must be old
  |
        CMP     r3, #ChangeDyn_SysHeap                  ; else sys heap is old
   [ :LNOT: NewStyle_RMA
        CMPNE   r3, #ChangeDyn_RMA                      ; and if RMA old as well, do 2 CMPs
   ]
  ]
        BNE     GetBlockEnd
        ADR     r4, StartAddrs+4
        LDR     r3, [r4, r3, LSL #2]
        LDR     r4, [stack, #4*9]
        ADD     r3, r3, r4                              ; start + size = end
        MOV     pc, lr
 ]

GetBlockEnd   ; R3 is area to get end of: return address in R3
        MOV     r1, r3
        ADR     r4, StartAddrs+4
        LDR     r3, [r4, r3, LSL #2]
        CMP     r1, #ChangeDyn_Screen                   ; screen ?
        MOVEQ   pc, lr
        ADR     r4, Current_Size+4
        LDR     r4, [r4, r1, LSL #2]
        LDR     r4, [r4]
        ADD     r3, r3, r4                              ; start + size = end
        MOV     pc, lr

StartAddrs
        &       0                               ; AplWork
 [ NewStyle_SysHeap
        &       &FE000000                       ; cause abort
 |
        &       SysHeapStart                    ; SysHeap
 ]
 [ NewStyle_RMA
        &       &FE000000                       ; cause abort
 |
        &       RMAAddress                      ; RMA
 ]
        &       ScreenEndAdr                    ; Screen
 [ NewStyle_SpriteArea
        &       &FE000000                       ; cause abort
 |
        &       SpriteSpaceAddress              ; sprites
 ]
 [ NewStyle_FontArea
        &       &FE000000                       ; cause abort
 |
        &       FontCacheAddress                ; fonts
 ]
 [ NewStyle_RAMDisc
        &       &FE000000                       ; cause abort
 |
        &       RAMDiscAddress                  ; RAMFS
 ]
 [ UseFreePool
        &       FreePoolAddress                 ; Free pool
 ]

; ExtendScreen - move memory into screen area
;
; in:   r0 -> logical address of end of first source area (either free pool or aplspace)
;       r5 = amount of memory being moved from first source area
;       r6 = page size
;       r9 = MEMC CR
;       r10 = total amount of memory being moved
;       r11 = number of source area
;       r12 = number of dest area


ExtendScreen

; screenpos -:= r10 (move all current blocks down)

        Push    "r5,r11"                ; save partial amount and src area number
        MOV     r2, #0
        VDWS    r5
        LDR     r5, [r5, #TotalScreenSize]
        RSB     r3, r5, #ScreenEndAdr
        SUB     r3, r3, r10             ; where new screen start is
50
        MOV     r11, #AP_Screen         ; access privileges for screen (includes CB bits in new world)
        BL      Call_CAM_Mapping
        ADD     r2, r2, #1
        ADD     r3, r3, r6
        SUBS    r5, r5, r6
        BNE     %BT50
        Pull    "r5,r11"

        ADD     r5, r3, r5              ; logaddr of end of first part (if split) or both otherwise

; r0 -> end of the source (AplSpace or FreePool)
        Push    "r7, r8, r10-r12"
55
        Push    "r2, r3, r5, pc"        ; save flags, etc. too
        ADRL    r3, PageShifts-1
        LDRB    r3, [r3, r6, LSR #12]
        MOV     r3, r2, LSL r3          ; r3 = pagesize*r2
        ADD     r3, r3, #ScreenEndAdr   ; physram addr of next screen block

        SUB     r0, r0, r6              ; address of last src block

        MOV     r1, #Service_ClaimFIQ   ; we may be moving FIQ workspace
        BL      Issue_Service
        ADD     r1, r0, r6              ; end marker

        TEQP    pc, #SVC_mode+I_bit     ; disable IRQs as we may be moving
        NOP                             ; IRQ workspace

; copy R6 bytes from nextscreenblock to last src block; the last
; src block MUST NOT be doubly mapped.

60
        LDMIA   r3!, {r2, r4, r5, r7, r8, r10, r11, r12}
        STMIA   r0!, {r2, r4, r5, r7, r8, r10, r11, r12}
        CMP     r0, r1
        BLT     %BT60

        LDR     r2, [stack]
        SUB     r0, r0, r6
        MOV     r3, #0
        LDR     r3, [r3, #CamEntriesPointer]    ; get address of soft CAM copy
 [ ExpandedCamMap
        ADD     r3, r3, r2, LSL #3              ; point at (address, PPL) for this page
        LDMIA   r3, {r3, r11}                   ; and load them
 |
        LDR     r3, [r3, r2, LSL #2]            ; curr addr of next screen block
        MOV     r11, r3, LSR #28                ; protection level
        BIC     r3, r3, #&F0000000
 ]

 [ UseFreePool
        BL      MoveCAMatR0toR3issuingPagesSafe
 |
        BL      MoveCAMatR0toR3                 ; last aplblock := nextscreenblock
 ]

        Pull    "r2, r3, r5, r7"                ; r7 has IRQ state to restore
        BVS     cambust2
                                                ; entry no in r2, logaddr in r3
        MOV     r11, #AP_Screen
        BL      Call_CAM_Mapping                ; nextscreenblock moves into place

        TEQP    pc, r7                          ; restore IRQ state
        NOP

        MOV     r1, #Service_ReleaseFIQ
        BL      Issue_Service
        ADD     r3, r3, r6
        ADD     r2, r2, #1

        CMP     r3, r5                          ; have we got to end of this part
        BNE     %BT55                           ; [no, so loop]

        CMP     r3, #ScreenEndAdr
        BEQ     %FT65

        MOV     r3, #ChangeDyn_AplSpace
        BL      GetBlockEnd                     ; get end of aplspace
        MOV     r0, r3                          ; r0 -> end of aplspace
        MOV     r3, r5                          ; continue dest where we left off
        MOV     r5, #ScreenEndAdr               ; finish only at end this time
        B       %BT55

65
        Pull    "r7, r8, r10-r12"
        B       %BT40

cambust2
        Pull    "r7, r8, r10-r12"
cambust
        STR     r0, [stack]
        Pull    "r0, r2-r6, r9, r10, lr"
        B      SLVK_SetV

 ]

; *** End of old style code ***

; Exit from ChangeDynamicArea with error Not all moved

 [ NewStyle_All
failure_IRQgoingClearSemaphore
        MOV     r0, #0
        STR     r0, [r0, #CDASemaphore]
 ]
failure_IRQgoing
        ADR     r0, ErrorBlock_ChDynamNotAllMoved
ChangeDynamic_Error
        MOV     r10, #0
        STR     r0, [stack]
        LDR     lr, [stack, #4*10]
        ORR     lr, lr, #V_bit
        STR     lr, [stack, #4*10]
CDS_PostServiceWithRestore
 [ (:LNOT: NewStyle_SysHeap) :LOR: (:LNOT: NewStyle_RMA)
        BL      testrestoreheapend
 ]
      [ International
        LDR     r0, [stack]
        BL      TranslateError
        STR     r0, [stack]
      ]

; and drop thru to ...

CDS_PostService
        MOV     r1, #Service_MemoryMoved
        MOV     r0, r10                 ; amount moved
        MOVS    r2, r11                 ; which way was transfer?
        BMI     %FT47                   ; [definitely a grow]
        CMP     r11, #ChangeDyn_FreePool
        BNE     %FT48                   ; [definitely a shrink]
        CMP     r12, #ChangeDyn_AplSpace
        BEQ     %FT48                   ; [a shrink]
47
        RSB     r0, r0, #0             ; APLwork or free was source
        MOV     r2, r12                ; r2 = area indicator
48
        BL      Issue_Service

        MOV     r1, r10                ; amount moved

     [ International
        Pull    "r0"
        LDR     lr, [sp, #9*4]
        TST     lr, #V_bit
        BLNE    TranslateError
        Pull    "r2-r9, r10, lr"
     |
        Pull    "r0, r2-r9, r10, lr"
     ]
        ExitSWIHandler

        MakeErrorBlock ChDynamNotAllMoved

 [ MEMM_Type = "ARM600"
  [ 1 = 1
; in:   r0 = logical address where page is now

GetPageFlagsForR0IntoR6 ENTRY "R0-R2, R4-R5, R7"
;
; code from MoveCAMatR0toR3
;
        LDR     r5, =L2PT
        ADD     r4, r5, r0, LSR #10             ; r4 -> L2PT for log addr r0
        MOV     r2, r4, LSR #12
        LDR     r2, [r5, r2, LSL #2]            ; r2 = L2PT entry for r4
        TST     r2, #3                          ; if no page there
        BEQ     %FT90                           ; then cam corrupt

        LDR     r4, [r4]                        ; r4 = L2PT entry for r0
        TST     r4, #3                          ; check entry is valid too
        BEQ     %FT91
        MOV     r4, r4, LSR #12                 ; r4 = phys addr >> 12

        MOV     r2, #0
        LDR     r6, [r2, #MaxCamEntry]
        MOV     r5, #PhysRamTable
10
        CMP     r2, r6                          ; if page we've got to is > max
        BHI     %FT92                           ; then corrupt
        LDMIA   r5!, {r7, lr}                   ; get phys.addr, size
        SUB     r7, r4, r7, LSR #12             ; number of pages into this bank
        CMP     r7, lr, LSR #12                 ; if too many
        ADDCS   r2, r2, lr, LSR #12             ; then advance physical page no.
        BCS     %BT10                           ; and loop

        ADD     r2, r2, r7                      ; add on number of pages within bank
;
; code from BangCamUpdate
;
        MOV     r1, #0
        LDR     r1, [r1, #CamEntriesPointer]
        ADD     r1, r1, r2, LSL #3              ; point at cam entry (logaddr, PPL)
        LDMIA   r1, {r0, r6}                    ; r0 = current logaddress, r6 = current PPL
        EXIT

90
        ADR     lr, NoL2ForPageBeingRemovedError ; NB don't corrupt r0 yet - we need that in block as evidence
95
        STR     lr, [sp]                        ; update returned r0
        BL      StoreDebugRegs
        PullEnv                                 ; seriously broken memory
        SETV
        MOV     pc, lr

91
        ADR     lr, PageBeingRemovedNotPresentError
        B       %BT95

92
        ADR     lr, PhysicalAddressNotFoundError
        B       %BT95


  ]
 ]

; MoveCAMatR0toR3
; in:   r0 = old logaddr
;       r3 = new logaddr
;       r9 = MEMC CR
;       r11 = page protection level
;
; out:  r2 = physical page number of page moved, unless there was a serious error
;       r0,r1,r3,r6-r12 preserved
;       r4,r5 corrupted

 [ MEMM_Type = "ARM600"
MoveCAMatR0toR3 ENTRY "r0,r1,r6,r7"
        LDR     r5, =L2PT
        ADD     r4, r5, r0, LSR #10             ; r4 -> L2PT for log addr r0
        MOV     r2, r4, LSR #12
        LDR     r2, [r5, r2, LSL #2]            ; r2 = L2PT entry for r4
        TST     r2, #3                          ; if no page there
        BEQ     %FT90                           ; then cam corrupt

        LDR     r4, [r4]                        ; r4 = L2PT entry for r0
        TST     r4, #3                          ; check entry is valid too
        BEQ     %FT91
        MOV     r4, r4, LSR #12                 ; r4 = phys addr >> 12

        MOV     r2, #0
        LDR     r6, [r2, #MaxCamEntry]
        MOV     r5, #PhysRamTable
10
        CMP     r2, r6                          ; if page we've got to is > max
        BHI     %FT92                           ; then corrupt
        LDMIA   r5!, {r7, lr}                   ; get phys.addr, size
        SUB     r7, r4, r7, LSR #12             ; number of pages into this bank
        CMP     r7, lr, LSR #12                 ; if too many
        ADDCS   r2, r2, lr, LSR #12             ; then advance physical page no.
        BCS     %BT10                           ; and loop

        ADD     r2, r2, r7                      ; add on number of pages within bank
        BL      BangCamUpdate
        CLRV
        EXIT

90
        ADR     lr, NoL2ForPageBeingRemovedError ; NB don't corrupt r0 yet - we need that in block as evidence
95
        STR     lr, [sp]                        ; update returned r0
        BL      StoreDebugRegs
        PullEnv                                 ; seriously broken memory
        SETV
        MOV     pc, lr

91
        ADR     lr, PageBeingRemovedNotPresentError
        B       %BT95

92
        ADR     lr, PhysicalAddressNotFoundError
        B       %BT95

StoreDebugRegs
        Push    "lr"
        MOV     lr, #CamMapCorruptDebugBlock
        STMIA   lr, {r0-lr}
        LDR     r0, [sp, #1*4]                  ; reload stacked r0 (error pointer)
        STR     r0, [lr, #15*4]                 ; store in stacked PC position
        Pull    "pc"

NoL2ForPageBeingRemovedError
        &       0
        =       "Memory Corrupt: No L2PT for page being removed", 0
        ALIGN

PageBeingRemovedNotPresentError
        &       0
        =       "Memory Corrupt: Page being removed was not present", 0
        ALIGN

PhysicalAddressNotFoundError
        &       0
        =       "Memory Corrupt: Physical address not found", 0
        ALIGN
 |

MoveCAMatR0toR3 ROUT
        MOV     r2, #0
        LDR     r4, [r2, #CamEntriesPointer]
        LDR     r2, [r2, #MaxCamEntry]
10
 [ ExpandedCamMap
        LDR     r5, [r4, r2, LSL #3]
 |
        LDR     r5, [r4, r2, LSL #2]
        BIC     r5, r5, #&F0000000
 ]
        CMP     r5, r0
        BEQ     Call_CAM_Mapping
        SUBS    r2, r2, #1
        BGE     %BT10

        ADR     r0, CamMapBroke
        ORRS    pc, lr, #V_bit
 ]

CamMapBroke
        &       0
        =       "!!!! CAM Map Corrupt !!!!", 0
        ALIGN
Call_CAM_Mapping
        Push    "r0, r1, r4, r6, lr"
        BL      BangCamUpdate
        Pull    "r0, r1, r4, r6, pc"

 [ UseFreePool :LAND: :LNOT: NewStyle_All

; MoveCAMatR0toR3issuingPagesSafe
; in:   r0 = old logaddr
;       r2 = old physical page number
;       r3 = new logaddr
;       r9 = MEMC CR
;       r11 = page protection level
;
; out:  r0,r1,r3,r6-r12 preserved
;       r2,r4,r5 corrupted
;
; Note: this still needs some serious work done to it to cope with doubly-mapped areas

MoveCAMatR0toR3issuingPagesSafe ENTRY "r0,r1,r3,r6,r7,r12", 6*4
        STR     r2, [sp, #0*4]                  ; store old page number at offset 0 in frame
        LDR     r5, =L2PT
        ADD     r4, r5, r0, LSR #10             ; r4 -> L2PT for log addr r0
        MOV     r2, r4, LSR #12
        LDR     r2, [r5, r2, LSL #2]            ; r2 = L2PT entry for r4
        TST     r2, #3                          ; if no page there
        BEQ     %FT90                           ; then cam corrupt

        LDR     r4, [r4]                        ; r4 = L2PT entry for r0
        TST     r4, #3                          ; check entry OK too
        BEQ     %FT91
        MOV     r12, r4, LSR #12                ; r12 = phys addr >> 12

        MOV     r2, #0
        LDR     r6, [r2, #MaxCamEntry]
        MOV     r5, #PhysRamTable
10
        CMP     r2, r6                          ; if page we've got to is >= max
        BHI     %FT92                           ; then corrupt
        LDMIA   r5!, {r7, lr}                   ; get phys.addr, size
        SUB     r7, r12, r7, LSR #12             ; number of pages into this bank
        CMP     r7, lr, LSR #12                 ; if too many
        ADDCS   r2, r2, lr, LSR #12             ; then advance physical page no.
        BCS     %BT10                           ; and loop

        ADD     r2, r2, r7                      ; add on number of pages within bank
        STR     r2, [sp, #3*4]                  ; store new page number at offset 3 in frame
        BL      BangCamUpdate
        EXIT    VS

; now check if page being snaffled is a L2 page, and if so, change L1 contents to point to new page

        SUBS    lr, r3, #L2PT                   ; check if destination page points in L2PT area
        BCC     %FT20                           ; below L2PT, so OK
        CMP     lr, #4*1024*1024                ; is offset into L2PT less than size of L2PT?
        BCS     %FT20                           ; no, so OK

        LDR     r1, =L1PT
        ADD     r1, r1, lr, LSR #(12-4)         ; address in L1 of 4 consecutive words to update
        LDR     r2, [r1]                        ; load 1st word, to get AP etc bits
        MOV     r2, r2, LSL #(31-9)             ; junk other bits
        MOV     r2, r2, LSR #(31-9)
        ORR     r2, r2, r12, LSL #12            ; merge with address bits
        STR     r2, [r1], #4
        ADD     r2, r2, #&400
        STR     r2, [r1], #4
        ADD     r2, r2, #&400
        STR     r2, [r1], #4
        ADD     r2, r2, #&400
        STR     r2, [r1], #4
20
; now issue the service

        MOV     r1, #Service_PagesSafe
        MOV     r2, #1                          ; 1 page at a time
        MOV     r3, sp                          ; 1st frame starts at sp
        ADD     r4, r3, #3*4                    ; 2nd frame starts at sp +12
        BL      Issue_Service
        CLRV
        EXIT

90
        ADR     lr, NoL2ForPageBeingRemovedError
95
        STR     lr, [sp]                        ; update returned r0
        BL      StoreDebugRegs
        PullEnv                                 ; seriously broken memory
        SETV
        MOV     pc, lr

91
        ADR     lr, PageBeingRemovedNotPresentError
        B       %BT95

92
        ADR     lr, PhysicalAddressNotFoundError
        B       %BT95

 ]

 [ :LNOT: NewStyle_RAMDisc
;........................................
; Old style RAMFS bashing

CheckRAMFSChangeOK
      Push   "r0-r5"
      MOV     r0, #5
      ADR     r1, ramcolondollardotstar
      SWI     XOS_File
      CMPVC   r0, #0
      Pull   "r0-r5"
      BVS     AllowRAMFSChange             ; ramfs not present
      BEQ     AllowRAMFSChange             ; ramfs empty
      ADR     r0, ErrorBlock_RAMFsUnchangeable
      B       ChangeDynamic_Error
      MakeErrorBlock RAMFsUnchangeable

ramcolondollardotstar = "ram:$.*",0
ramfsname = "ramfs",0

      ALIGN

reinitialise_RAMFS
      Push   "r0-r6"
      MOV     r0, #ModHandReason_EnumerateROM_Modules
      MOV     r1, #0
      MOV     r2, #-1
look_for_RAMFS
      SWI     XOS_Module
      BVS     OKtoreinitRAMFS        ; can't find it: may be in ram
      ADR     r5, ramfsname
nameloop
      LDRB    r6, [r3], #1
      CMP     r6, #" "
      BLE     foundramfs
      LowerCase r6, lr
      LDRB    lr, [r5], #1
      CMP     lr, r6
      BEQ     nameloop
      B       look_for_RAMFS

foundramfs
      CMP     r4, #-1
      BNE     OKtoreinitRAMFS
      Pull   "r0-r6"
      B       CDS_PostService

OKtoreinitRAMFS
      MOV     r0, #ModHandReason_ReInit
      ADR     r1, ramfsname
      SWI     XOS_Module
      Pull   "r0-r6"
      B       CDS_PostService
 ]

; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++
; In    r0 bits 0..6 = area number
;       r0 bit 7 set => return max area size in r2 (implemented 13 Jun 1990)
;                       this will return an error if not implemented
; Out   r0 = address of area
;       r1 = current size of area
;       r2 = max size of area if r0 bit 7 set on entry (preserved otherwise)

; TMD 19-May-93: When this is updated to new CDA list, change meaning as follows:

; r0 in range 0..&7F    return address, size of area r0
;             &80..&FF  return address, size, maxsize of area (r0-&80)
;             &100..    return address, size, maxsize of area r0

; TMD 20-Aug-93: New bit added - if r0 = -1 on entry, then returns info on application space
; r0 = base address (&8000)
; r1 = current size (for current task)
; r2 = maximum size (eg 16M-&8000)

ReadDynamicArea ROUT

readdyn_returnR2bit     *       &80
        ASSERT  ChangeDyn_MaxArea < readdyn_returnR2bit

 [ NewCDA
        CMP     r0, #-1                         ; if finding out about app space
        LDREQ   r1, [r0, #AplWorkSize+1]        ; then r1 = current size
        LDREQ   r2, =AplWorkMaxSize             ; and r2 = max size
        MOVEQ   r0, #&8000                      ; r0 = base address
        SUBEQ   r1, r1, r0                      ; adjust size and maxsize
        SUBEQ   r2, r2, r0                      ; to remove bottom 32K
        ExitSWIHandler EQ

; first check if it's one of the new ones

        Push    "r1,lr"
        CMP     r0, #&100                       ; if area >= &100
        MOVCS   r1, r0                          ; then just use area
        BICCC   r1, r0, #readdyn_returnR2bit    ; else knock off bit 7
        BL      CheckAreaNumber                 ; out: r10 -> node
        Pull    "r1,lr"
        BCC     %FT05                           ; [not a new one, so use old code]

        CMP     r0, #&80                        ; CS => load maxsize into R2
                                                ; (do this either if bit 7 set, or area >=&100)
        LDRCS   r2, [r10, #DANode_MaxSize]
        LDR     r1, [r10, #DANode_Size]         ; r1 = current size
        LDR     r0, [r10, #DANode_Base]         ; r0 -> base
        LDR     r11, [r10, #DANode_Flags]       ; if doubly mapped
        TST     r11, #DynAreaFlags_DoublyMapped
        SUBNE   r0, r0, r1                      ; then return start of 1st copy for compatibility
        ExitSWIHandler
05
 ]
 [ :LNOT: NewStyle_All
        BIC     r10, r0, #readdyn_returnR2bit
        CMP     r10, #ChangeDyn_MaxArea
        BLS     %FT07
 ]
        ADRL    r0, ErrorBlock_BadDynamicArea
      [ International
        Push    "lr"
        BL      TranslateError
        Pull    "lr"
      ]
        B       SLVK_SetV

 [ :LNOT: NewStyle_All
07
        TST     r0, #readdyn_returnR2bit        ; if bit 7 set, R2 = max size of area
  [ MEMC_Type = "IOMD"
        BEQ     %FT10
        EORS    r11, r10, #ChangeDyn_Screen     ; if screen
        LDREQ   r2, [r11, #VideoSize]           ; then use video size
        ADRNEL  r11, Grow_LimitsPtrs+4
        LDRNE   r2, [r11, r10, LSL #2]          ; else use grow limits
        LDRNE   r2, [r2]                        ; (grow limits are pointers to max sizes now)
10
  |
        ADRNEL  r11, Grow_LimitsPtrs+4
        LDRNE   r2, [r11, r10, LSL #2]
        LDRNE   r2, [r2]                        ; (grow limits are pointers to max sizes now)
  ]

        CMP     r10, #ChangeDyn_Screen    ; screen?
        ADRL    r0, Current_Size+4
        ADRL    r11, StartAddrs+4
        LDR     r1, [r0, r10, LSL #2]
        LDR     r1, [r1]                  ; r1 = current size of area
        LDR     r0, [r11, r10, LSL #2]    ; r0 = start address of area
        SUBEQ   r0, r0, r1                ; screen goes wackbords
        B       SLVK
 ]

        MakeErrorBlock  BadDynamicArea

; *************************************************************************
; User access to CAM mapping
; ReadMemMapInfo:
; returns R0 = pagsize
;         R1 = number of pages in use  (= R2 returned from SetEnv/Pagesize)
; *************************************************************************

ReadMemMapInfo_Code
      MOV      R10, #0
      LDR      R0, [R10, #Page_Size]
      LDR      R1, [R10, #RAMLIMIT]    ; = total memory size
      ADRL     R11, PageShifts-1
      LDRB     R11, [R11, R0, LSR #12]
      MOV      R1, R1, LSR R11
      ExitSWIHandler

; ************************************************************************
; SWI ReadMemMapEntries: R0 pointer to list.
;  Entries are three words long, the first of which is the CAM page number.
;  List terminated by -1.
; Returns pagenumber (unaltered)/address/PPL triads as below
; ************************************************************************

ReadMemMapEntries_Code  ROUT
        Push    "r0,r14"
        MOV     r14, #0
        LDR     r10, [r14, #CamEntriesPointer]
        LDR     r14, [r14, #MaxCamEntry]
01
        LDR     r12, [r0], #4
        CMP     r12, r14
        Pull    "r0,r14", HI
        ExitSWIHandler HI
 [ ExpandedCamMap
        ADD     r11, r10, r12, LSL #3
        LDMIA   r11, {r11, r12}
 |
        LDR     r11, [r10, r12, LSL #2]
        MOV     r12, r11, LSR #28               ; PPL
        BIC     r11, r11, #&F0000000
 ]
        STMIA   r0!, {r11, r12}
        B       %BT01

; ************************************************************************
; SWI FindMemMapEntries:
; In:  R0 -> table of 12-byte page entries
;       +0      4       probable page number (0..npages-1) (use 0 if no idea)
;       +4      4       logical address to match with
;       +8      4       undefined
;       terminated by a single word containing -1
;
; Out: table of 12-byte entries updated:
;       +0      4       actual page number (-1 => not found)
;       +4      4       address (preserved)
;       +8      4       page protection level (3 if not found)
;       terminator preserved
;
; ************************************************************************

FindMemMapEntries_Code  ROUT
 [ ExpandedCamMap

; Code for expanded CAM map version

        Push    "r0, r9, r14"
        MOV     r14, #0
        LDR     r9, [r14, #MaxCamEntry]
        LDR     r14, [r14, #CamEntriesPointer]  ; r14 -> start of cam map
        ADD     r9, r14, r9, LSL #3             ; r9 -> first word of last entry in cam map
10
        LDR     r10, [r0, #0]                   ; r10 = guess page number (or -1)
        CMP     r10, #-1                        ; if -1 then end of list
        Pull    "r0, r9, r14", EQ               ; so restore registers
        ExitSWIHandler EQ                       ; and exit

        LDR     r11, [r0, #4]                   ; r11 = logical address
        ADD     r10, r14, r10, LSL #3           ; form address with 'guess' page
        CMP     r10, r9                         ; if off end of CAM
        BHI     %FT20                           ; then don't try to use the guess

        LDR     r12, [r10]                      ; load address from guessed page
        TEQ     r11, r12                        ; compare address
        BEQ     %FT60                           ; if equal, then guessed page was OK
20

; for now, cheat by looking in L2PT, to see if we can speed things up

        Push    "r5-r8"                         ; need some registers here!
        LDR     r10, =L2PT
        MOV     r8, r11, LSR #12                ; r8 = logical page number
        ADD     r8, r10, r8, LSL #2             ; r8 -> L2PT entry for log.addr
        MOV     r5, r8, LSR #12                 ; r5 = page offset to L2PT entry for log.addr
        LDR     r5, [r10, r5, LSL #2]           ; r5 = L2PT entry for L2PT entry for log.addr
        TST     r5, #3                          ; if page not there
        SUBEQ   r10, r9, #8                     ; then invalid page so go from last one
        BEQ     %FT45
        LDR     r8, [r8]                        ; r8 = L2PT entry for log.addr
        MOV     r8, r8, LSR #12                 ; r8 = physaddr / 4K

        MOV     r5, #PhysRamTable
        SUB     r10, r14, #8
30
        CMP     r10, r9                         ; have we run out of RAM banks?
        BCS     %FT40                           ; then fail
        LDMIA   r5!, {r6,r7}                    ; load next address, size
        SUB     r6, r8, r6, LSR #12             ; number of pages into this bank
        CMP     r6, r7, LSR #12                 ; if more than there are
        ADDCS   r10, r10, r7, LSR #12-3         ; then advance CAM entry position
        BCS     %BT30                           ; and loop to next bank

        ADD     r10, r10, r6, LSL #3            ; advance by 2 words for each page in this bank
40
        SUBCS   r10, r9, #8                     ; search from last one, to fail quickly (if CS)
45
        Pull    "r5-r8"
50
        CMP     r10, r9                         ; if not just done last one,
        LDRNE   r12, [r10, #8]!                 ; then get logical address
        TEQNE   r11, r12                        ; compare address
        BNE     %BT50                           ; loop if not same and not at end

; either found page or run out of pages

        TEQ     r11, r12                        ; see if last one matched
                                                ; (we always load at least one!)
60
        LDREQ   r12, [r10, #4]                  ; if match, then r12 = PPL
        SUBEQ   r10, r10, r14                   ; and page number=(r10-r14)>>3
        MOVEQ   r10, r10, LSR #3

        MOVNE   r10, #-1                        ; else unknown page number indicator
        MOVNE   r12, #3                         ; and PPL=3 (no user access)

        STMIA   r0!, {r10-r12}                  ; store all 3 words
        B       %BT10                           ; and go back for another one
 |

; Code for non-expanded CAM map version

        Push    "r0, r9, r14"
        MOV     r14, #0
        LDR     r9, [r14, #MaxCamEntry]
        LDR     r14, [r14, #CamEntriesPointer]  ; r14 -> start of cam map
        ADD     r9, r14, r9, LSL #2             ; r9 -> last entry in cam map
10
        LDR     r10, [r0, #0]                   ; r10 = guess page number (or -1)
        CMP     r10, #-1                        ; if -1 then end of list
        Pull    "r0, r9, r14", EQ               ; so restore registers
        ExitSWIHandler EQ                       ; and exit

        LDR     r11, [r0, #4]                   ; r11 = logical address
        MOV     r11, r11, LSL #4                ; shift up so we can compare with
                                                ; shifted up addresses
        ADD     r10, r14, r10, LSL #2           ; form address with 'guess' page
        CMP     r10, r9                         ; if off end of CAM
        BHI     %FT15                           ; then don't try to use the guess

        LDR     r12, [r10]                      ; load address+ppl from guessed page
        TEQ     r11, r12, LSL #4                ; compare address
        BEQ     %FT30                           ; if equal, then guessed page was OK
15
 [ MEMM_Type = "ARM600"

; for now, cheat by looking in L2PT, to see if we can speed things up

        Push    "r5-r8"                         ; need some registers here!
        LDR     r10, =L2PT
        CMP     r11, #256*1024*1024*4           ; if address >= 256M
        BCS     %FT17                           ; then invalid, so search from last one

        MOV     r8, r11, LSR #16                ; r8 = logaddr / 4K
        LDR     r8, [r10, r8, LSL #2]           ; get page table entry
        MOV     r8, r8, LSR #12                 ; r8 = physaddr / 4K

        MOV     r5, #VideoPhysAddr
        SUB     r10, r14, #4
16
        CMP     r10, r9                         ; have we run out of RAM banks?
        BCS     %FT17                           ; then fail
        LDMIA   r5!, {r6,r7}                    ; load next address, size
        SUB     r6, r8, r6, LSR #12             ; number of pages into this bank
        CMP     r6, r7, LSR #12                 ; if more than there are
        ADDCS   r10, r10, r7, LSR #12-2         ; then advance CAM entry position (bank size must be multiple of 4K)
        BCS     %BT16                           ; and loop to next bank

        ADD     r10, r10, r6, LSL #2            ; advance by 1 word for each page in this bank
17
        SUBCS   r10, r9, #4                     ; search from last one, to fail quickly (if CS)
        Pull    "r5-r8"
 |
        SUB     r10, r14, #4                    ; move pointer to start of CAM -4
 ]

20
        CMP     r10, r9                         ; if not just done last one, get
        LDRNE   r12, [r10, #4]!                 ; address in bits 0..27, PPL in 28..31
        TEQNE   r11, r12, LSL #4                ; compare address
        BNE     %BT20                           ; loop if not same and not at end

; either found page or run out of pages

        TEQ     r11, r12, LSL #4                ; see if last one matched
                                                ; (we always load at least one!)
30
        SUBEQ   r10, r10, r14                   ; if match, then
        MOVEQ   r10, r10, LSR #2                ; page number=(r10-r14)>>2
        MOVEQ   r12, r12, LSR #28               ; and PPL=r12>>28

        MOVNE   r10, #-1                        ; else unknown page number indicator
        MOVNE   r12, #3                         ; and PPL=3 (no user access)

        MOV     r11, r11, LSR #4                ; restore r11 to original value

        STMIA   r0!, {r10-r12}                  ; store all 3 words
        B       %BT10                           ; and go back for another one
 ]

;**************************************************************************
; SWI SetMemMapEntries: R0 pointer to list of CAM page/address/PPL triads,
;  terminated by -1.
; Any address > 32M means "put the page out of the way"
; +++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++++

SetMemMapEntries_Code  ROUT
        Push    "r0-r6, r9, lr"
        MOV     r12, r0

; BangCamUpdate takes entry no in r2, logaddr to set to in r3
; r9 current MEMC, r11 = PPL
; corrupts r0,r1,r4,r6

        MOV     r9, #0
        LDR     r5, [r9, #MaxCamEntry]
        LDR     r9, [r9, #MEMC_CR_SoftCopy]
01
        LDR     r2, [r12], #4
        CMP     r2, r5
        BHI     %FT02                   ; finished
        LDMIA   r12!, {r3, r11}
        AND     r11, r11, #3
 [ MEMM_Type = "ARM600"
        CMP     r3, #-1
 |
        CMP     r3, #32*1024*1024
 ]
        LDRHS   r3, =DuffEntry
        MOVHS   r11, #AP_Duff
        BL      BangCamUpdate
        B       %BT01
02
        Pull    "r0-r6, r9, lr"
        ExitSWIHandler

        LTORG

 [ :LNOT: NewCDA
InitDynamicAreas        MOV     pc, lr          ; if not new world then nothing to initialise
 ]

 [ NewCDA

;**************************************************************************
;
;       DynamicAreaSWI - Code to handle SWI OS_DynamicArea
;
; in:   r0 = reason code
;       Other registers depend on reason code
;
; out:  Depends on reason code
;

DAReason_Create *       0
DAReason_Remove *       1
DAReason_GetInfo *      2
DAReason_Enumerate *    3
DAReason_Renumber *     4
DAReason_Limit  *       5

DynArea_NewAreas *      &100            ; Allocated area numbers start here
DynArea_NewAreasBase *  &04000000       ; Allocated area addresses start here

; Bits in dynamic area flags (and page flags)

DynAreaFlags_APBits     *       15 :SHL: 0      ; currently only uses 2 bits, but may extend to allow svc/usr read-only
DynAreaFlags_NotBufferable *    1 :SHL: 4
DynAreaFlags_NotCacheable *     1 :SHL: 5
DynAreaFlags_DoublyMapped *     1 :SHL: 6
DynAreaFlags_NotUserDraggable * 1 :SHL: 7
 [ DAF_SpecifyBit
DynAreaFlags_NeedsSpecificPages *  1 :SHL: 8    ; whether area will ever require particular physical pages
 ]
DynAreaFlags_AccessMask *       DynAreaFlags_APBits :OR: DynAreaFlags_NotBufferable :OR: DynAreaFlags_NotCacheable :OR: DynAreaFlags_DoublyMapped

; The following bits are only present in page flags

TempUncacheableShift    *       9
PageFlags_TempUncacheableBits   * 15 :SHL: TempUncacheableShift    ; temporary count of uncacheability, used by DMA mgr
PageFlags_Unavailable   *       1 :SHL: 13      ; physical page may not be requested by a PreShrink handler

; Temporary flags only used by kernel

PageFlags_Required      *       1 :SHL: 14      ; physical page asked for by handler

DynamicAreaSWI ENTRY
        BL      DynAreaSub
        PullEnv
        ORRVS   lr, lr, #V_bit
        ExitSWIHandler

DynAreaSub
        CMP     r0, #DAReason_Limit
        ADDCC   pc, pc, r0, LSL #2
        B       DynArea_Unknown
        B       DynArea_Create
        B       DynArea_Remove
        B       DynArea_GetInfo
        B       DynArea_Enumerate
        B       DynArea_Renumber

; unknown OS_DynamicArea reason code

DynArea_Unknown
        ADRL    r0, ErrorBlock_HeapBadReason
DynArea_TranslateAndReturnError
      [ International
        Push    lr
        BL      TranslateError
        Pull    lr
      ]
DynArea_ReturnError
        SETV
        MOV     pc, lr

;**************************************************************************
;
;       DynArea_Create - Create a dynamic area
;
;       Internal routine called by DynamicAreaSWI and by reset code
;
; in:   r0 = reason code (0)
;       r1 = new area number, or -1 => RISC OS allocates number
;       r2 = initial size of area (in bytes)
;       r3 = base logical address of area, or -1 => RISC OS allocates address space
;       r4 = area flags
;               bits 0..3 = access privileges
;               bit  4 = 1 => not bufferable
;               bit  5 = 1 => not cacheable
;               bit  6 = 0 => area is singly mapped
;                      = 1 => area is doubly mapped
;               bit  7 = 1 => area is not user draggable in TaskManager window
;               bits 8..31 = 0 (bits 8..12 are used in page flags, but not for areas)
;
;       r5 = maximum size of area, or -1 for total RAM size
;       r6 -> area handler routine
;       r7 = workspace pointer for area handler (-1 => use base address)
;       r8 -> area description string (null terminated) (gets copied)
;
; out:  r1 = given or allocated area number
;       r3 = given or allocated base address of area
;       r5 = given or allocated maximum size
;       r0, r2, r4, r6-r9 preserved
;       r10-r12 may be corrupted
;

DynArea_Create ENTRY "r2,r6-r8"
        CMP     r1, #-1         ; do we have to allocate a new area number
        BEQ     %FT10

        BL      CheckAreaNumber ; see if area number is unique
        BCC     %FT20           ; didn't find it, so OK

        ADR     r0, ErrorBlock_AreaAlreadyExists
DynArea_ErrorTranslateAndExit
        PullEnv
        B       DynArea_TranslateAndReturnError

        MakeErrorBlock  AreaAlreadyExists
        MakeErrorBlock  AreaNotOnPageBdy
        MakeErrorBlock  OverlappingAreas
        MakeErrorBlock  CantAllocateArea
        MakeErrorBlock  CantAllocateLevel2
        MakeErrorBlock  UnknownAreaHandler

; we have to allocate an area number for him

10
        MOV     r1, #DynArea_NewAreas
12
        BL      CheckAreaNumber
        ADDCS   r1, r1, #1      ; that area number already exists, so increment
        BCS     %BT12           ; and try again
20

; now validate maximum size of area

        MOV     r10, #0
        LDR     r11, [r10, #Page_Size]
        LDR     r10, [r10, #RAMLIMIT]   ; get total RAM size
        CMP     r5, r10                 ; if requested maximum size is > total
        MOVHI   r5, r10                 ; then set max to total (NB. -1 passed in always yields HI)

        SUB     r10, r11, #1            ; also round up to a page multiple
        ADD     r5, r5, r10
        BIC     r5, r5, r10

; now see if we have to allocate a logical address space

        CMP     r3, #-1                 ; if we are to allocate the address space
        BEQ     %FT30                   ; then go do it

; otherwise we must check that the address does not clash with anything else

        TST     r3, r10                         ; does it start on a page boundary
        ADRNE   r0, ErrorBlock_AreaNotOnPageBdy ; if not then error
        BNE     DynArea_ErrorTranslateAndExit

        BL      CheckForOverlappingAreas        ; in: r3 = address, r4 = flags, r5 = size; out: if error, r0->error, V=1
        BVC     %FT40
25
        PullEnv
        B       DynArea_ReturnError

30
        BL      AllocateAreaAddress             ; in: r4 = flags, r5 = size of area needed; out: r3, or V=1, r0->error
        BVS     %BT25
40
        BL      AllocateBackingLevel2           ; in: r3 = address, r4 = flags, r5 = size; out: VS if error
        BVS     %BT25

        Push    "r0,r1,r3"
        MOV     r3, #DANode_NodeSize
        BL      ClaimSysHeapNode                ; out: r2 -> node
        STRVS   r0, [sp]
        Pull    "r0,r1,r3"
        BVS     %BT25                           ; failed to claim node

; now store data in node (could probably use STM if we shuffled things around)

        CMP     r7, #-1                         ; if workspace ptr = -1
        MOVEQ   r7, r3                          ; then use base address

        STR     r1, [r2, #DANode_Number]
        STR     r3, [r2, #DANode_Base]
        STR     r4, [r2, #DANode_Flags]
        STR     r5, [r2, #DANode_MaxSize]
        STR     r6, [r2, #DANode_Handler]
        STR     r7, [r2, #DANode_Workspace]
        MOV     r7, #0                          ; initial size is zero
        STR     r7, [r2, #DANode_Size]          ; before we grow it

; now make copy of string - first find out length of string

        MOV     r7, r8
45
        LDRB    r6, [r7], #1
        TEQ     r6, #0
        BNE     %BT45

        Push    "r0-r3"
        SUB     r3, r7, r8                      ; r3 = length inc. term.
        BL      ClaimSysHeapNode
        STRVS   r0, [sp]
        MOV     r7, r2
        Pull    "r0-r3"
        BVS     StringNodeClaimFailed

        STR     r7, [r2, #DANode_Title]
50
        LDRB    r6, [r8], #1                    ; copy string into claimed block
        STRB    r6, [r7], #1
        TEQ     r6, #0
        BNE     %BT50

; now put node on list - list is sorted in ascending base address order

        MOV     r8, #DAList
        LDR     r6, [r2, #DANode_Base]
60
        MOV     r7, r8
        ASSERT  DANode_Link = 0
        LDR     r8, [r7, #DANode_Link]          ; get next node
        TEQ     r8, #0                          ; if no more
        BEQ     %FT70                           ; then put it on here
        LDR     lr, [r8, #DANode_Base]
        CMP     lr, r6                          ; if this one is before ours
        BCC     %BT60                           ; then loop

70
        STR     r8, [r2, #DANode_Link]
        STR     r2, [r7, #DANode_Link]

; now we need to grow the area to its requested size

        Push    "r0, r1"
        LDR     r0, [r2, #DANode_Number]
        LDR     r1, [sp, #2*4]                  ; reload requested size off stack
        SWI     XOS_ChangeDynamicArea
        BVS     %FT90

; Now issue service to tell TaskManager about it

        MOV     r2, r0                          ; r2 = area number
        MOV     r1, #Service_DynamicAreaCreate
        BL      Issue_Service
        Pull    "r0, r1"

        CLRV
        EXIT

90

; The dynamic area is not being created, because we failed to grow the area to the required size.
; The area itself will have no memory allocated to it (since if grow fails it doesn't move any).
; We must delink the node from our list, free the string node, and then the area node itself.

        STR     r0, [sp, #0*4]                  ; remember error pointer in stacked r0
        STR     r8, [r7, #DANode_Link]          ; delink area
        MOV     r6, r2                          ; save pointer to DANode itself
        LDR     r2, [r6, #DANode_Title]
        BL      FreeSysHeapNode                 ; free title string node
        MOV     r2, r6                          ; point r2 back at DANode
        Pull    "r0, r1"                        ; pull stacked registers, and drop thru to...

; The dynamic area is not being created, because there is no room to allocate space for the title string
; We must free the DANode we have allocated
; It would be nice to also free the backing L2, but we'll leave that for now.

; in: r2 -> DANode

StringNodeClaimFailed
        Push    "r0, r1"
        BL      FreeSysHeapNode
        Pull    "r0, r1"
        PullEnv
        B       DynArea_ReturnError

;**************************************************************************
;
;       DynArea_Remove - Remove a dynamic area
;
;       Internal routine called by DynamicAreaSWI
;
; in:   r0 = reason code (1)
;       r1 = area number
;
; out:  r10-r12 may be corrupted
;       All other registers preserved
;

DynArea_Remove ENTRY
        BL      CheckAreaNumber         ; check that area is there
        BCC     UnknownDyn              ; [not found]

; First try to shrink area to zero size

        Push    "r0-r2"
        MOV     r0, r1                  ; area number
        LDR     r2, [r10, #DANode_Size] ; get current size
        RSB     r1, r2, #0              ; negate it
        SWI     XOS_ChangeDynamicArea
        BVS     %FT80
        STRVS   r0, [sp]
        Pull    "r0-r2"
        EXIT    VS

; Issue service to tell TaskManager

        Push    "r1, r2"
        MOV     r2, r1
        MOV     r1, #Service_DynamicAreaRemove
        BL      Issue_Service
        Pull    "r1, r2"

; Now just de-link from list (r10 -> node, r11 -> prev)

        LDR     lr, [r10, #DANode_Link] ; store our link
        STR     lr, [r11, #DANode_Link] ; in prev link

        Push    "r0-r2"
        LDR     r2, [r10, #DANode_Title]        ; free title string block
        BL      FreeSysHeapNode
        MOV     r2, r10                         ; and free node block
        BL      FreeSysHeapNode
        Pull    "r0-r2"
        CLRV
        EXIT

; come here if shrink failed - r0-r2 stacked

80
        STR     r0, [sp]                ; overwrite stacked r0 with error pointer
        LDR     r0, [sp, #1*4]          ; reload area number
        LDR     r1, [r10, #DANode_Size] ; get size after failed shrink
        SUB     r1, r2, r1              ; change needed to restore original size
        SWI     XOS_ChangeDynamicArea   ; ignore any error from this
        SETV
        EXIT

UnknownDyn
        ADRL    r0, ErrorBlock_BadDynamicArea
 [ International
        BL      TranslateError
 ]
90
        SETV
        EXIT

;**************************************************************************
;
;       DynArea_GetInfo - Get info on a dynamic area
;
;       Internal routine called by DynamicAreaSWI
;
; in:   r0 = reason code (2)
;       r1 = area number
;
; out:  r2 = current size of area
;       r3 = base logical address
;       r4 = area flags
;       r5 = maximum size of area
;       r6 -> area handler routine
;       r7 = workspace pointer
;       r8 -> title string
;       r10-r12 may be corrupted
;       All other registers preserved
;

DynArea_GetInfo ALTENTRY
        BL      CheckAreaNumber         ; check area exists
        BCC     UnknownDyn              ; [it doesn't]

; r10 -> node, so get info

        LDR     r2, [r10, #DANode_Size]
        LDR     r3, [r10, #DANode_Base]
        LDR     r4, [r10, #DANode_Flags]
        LDR     r5, [r10, #DANode_MaxSize]
        LDR     r6, [r10, #DANode_Handler]
        LDR     r7, [r10, #DANode_Workspace]
        LDR     r8, [r10, #DANode_Title]
        CLRV
        EXIT

;**************************************************************************
;
;       DynArea_Enumerate - Enumerate dynamic areas
;
;       Internal routine called by DynamicAreaSWI
;
; in:   r0 = reason code (3)
;       r1 = -1 to start enumeration, or area number to continue from
;
; out:  r1 = next area number or -1 if no next
;       r10-r12 may be corrupted
;       All other registers preserved

DynArea_Enumerate ALTENTRY
        CMP     r1, #-1                         ; if starting from beginning
        LDREQ   r10, [r1, #DAList+1]            ; then load pointer to 1st node
        BEQ     %FT10                           ; and skip

        BL      CheckAreaNumber                 ; else check valid area number
        BCC     UnknownDyn                      ; complain if passed in duff area number

        LDR     r10, [r10, #DANode_Link]        ; find next one
10
        TEQ     r10, #0                         ; if at end
        MOVEQ   r1, #-1                         ; then return -1
        LDRNE   r1, [r10, #DANode_Number]       ; else return number
        CLRV
        EXIT

;**************************************************************************
;
;       DynArea_Renumber - Renumber dynamic area
;
;       Internal routine called by DynamicAreaSWI
;
; in:   r0 = reason code (4)
;       r1 = old area number
;       r2 = new area number
;

DynArea_Renumber ALTENTRY
        BL      CheckAreaNumber                 ; check valid area number
        BCC     UnknownDyn                      ; [it's not]

        Push    "r1"
        MOV     r12, r10                        ; save pointer to node
        MOV     r1, r2
        BL      CheckAreaNumber                 ; check area r2 doesn't already exist
        Pull    "r1"
        BCS     %FT90                           ; [area r2 already exists]

        STR     r2, [r12, #DANode_Number]

; Now issue service to tell TaskManager

        Push    "r1-r3"
        MOV     r3, r2                          ; new number
        MOV     r2, r1                          ; old number
        MOV     r1, #Service_DynamicAreaRenumber
        BL      Issue_Service
        Pull    "r1-r3"

        CLRV
        EXIT

90
        ADRL    r0, ErrorBlock_AreaAlreadyExists
 [ International
        BL      TranslateError
 ]
        SETV
        EXIT

;**************************************************************************
;
;       CheckAreaNumber - Try to find area with number r1
;
;       Internal routine called by DynArea_Create
;
; in:   r1 = area number to match
; out:  If match, then
;         C=1, r10 -> node, r11 -> previous node
;       else
;         C=0, r10,r11 corrupted
;       endif

CheckAreaNumber ENTRY
        MOV     r10, #DAList
        ASSERT  DANode_Link = 0                 ; because DAList has only link
10
        MOV     r11, r10                        ; save prev
        LDR     r10, [r10, #DANode_Link]        ; and load next
        CMP     r10, #1                         ; any more nodes?
        EXIT    CC                              ; no, then no match
        LDR     lr, [r10, #DANode_Number]       ; get number
        CMP     lr, r1                          ; does number match
        BNE     %BT10                           ; no, try next
        EXIT                                    ; (C=1 from CMP lr,r1)

;**************************************************************************
;
;       CheckForOverlappingAreas - Check that given area does not overlap any existing ones
;
;       Internal routine called by DynArea_Create
;
; in:   r3 = base address
;       r4 = area flags (NB if doubly mapped, then have to check both halves for overlap)
;       r5 = size (of each half in doubly mapped areas)
;
; out:  If this area overlaps with an existing one, then
;         r0 -> error
;         V=1
;       else
;         r0 preserved
;         V=0
;       endif
;

CheckForOverlappingAreas ENTRY "r0-r5"
        TST     r4, #DynAreaFlags_DoublyMapped          ; check if doubly mapped
        BEQ     %FT05                                   ; [not, so don't mangle]

        SUBS    r3, r3, r5                              ; move start address back
        BCC     %FT20                                   ; oh dear! - it went back to below 0
        MOVS    r5, r5, LSL #1                          ; and double size
        BCS     %FT20                                   ; if that wrapped then that's bad, too
05
        ADDS    r5, r5, r3                              ; r5 -> end +1
        BHI     %FT20                                   ; if CS, indicating wrap, and not EQ (ie just ending at 0), then bad

; First, check against list of fixed areas

        ADR     lr, FixedAreasTable
10
        LDMIA   lr!, {r0, r1}                           ; r0 = start addr, r1 = size
        CMP     r0, #-1                                 ; if at end of list
        BEQ     %FT30                                   ; then OK wrt fixed areas
        ADD     r1, r1, r0                              ; r1 = end addr+1
        CMP     r5, r0                                  ; if end of our area is <= start of fixed, then OK wrt fixed areas
        BLS     %FT30
        CMP     r3, r1                                  ; if start of our area is >= end of fixed, then go onto next area
        BCS     %BT10

20
        ADRL    r0, ErrorBlock_OverlappingAreas
 [ International
        BL      TranslateError
 ]
        STR     r0, [sp]
        SETV
        EXIT

; Now, check against DAList

30
        MOV     lr, #DAList
        ASSERT  DANode_Link = 0
40
        LDR     lr, [lr, #DANode_Link]
        CMP     lr, #0                                  ; if got to end of list (V=0)
        BEQ     %FT50                                   ; then exit saying OK
        LDR     r0, [lr, #DANode_Base]
        LDR     r1, [lr, #DANode_Flags]
        TST     r1, #DynAreaFlags_DoublyMapped
        LDR     r1, [lr, #DANode_MaxSize]
        SUBNE   r0, r0, r1                              ; if doubly mapped then move back
        MOVNE   r1, r1, LSL #1                          ; and double size
        ADD     r1, r1, r0                              ; r1 -> end
        CMP     r5, r0                                  ; if end of our area is <= start of dyn, then OK wrt dyn areas)
        BLS     %FT50
        CMP     r3, r1                                  ; if start of our area is >= end of dyn, then go onto next area
        BCS     %BT40
        B       %BT20                                   ; else it overlaps

50
        CLRV                                            ; OK exit
        EXIT


FixedAreasTable                                         ; table of fixed areas (address, size)
        &       0,                      AplWorkMaxSize  ; application space
 [ :LNOT: NewStyle_RMA
        &       RMAAddress,             RMAMaxSize      ; RMA (to be removed from here eventually)
 ]
 [ :LNOT: NewStyle_SysHeap
        &       SysHeapChunkAddress,    SysHeapMaxSize+SVCStackSize   ; system heap (to be removed eventually)
 ]
        &       UndStackSoftCamChunk,   1024*1024               ; undefined stack / soft cam map
        &       CursorChunkAddress,     64*1024                 ; 32K for cursor, 32K for "nowhere"
        &       L2PT,                   4*1024*1024             ; L2PT (and L1PT)
        &       &03000000,              16*1024*1024            ; I/O + ROM
 [ :LNOT: NewStyle_Screen
        &       ScreenEndAdr-16*1024*1024, 32*1024*1024         ; Screen (removable later)
 ]
 [ :LNOT: NewStyle_FontArea
        &       FontCacheAddress,      FontCacheMaxSize ; Font cache (removable later)
 ]
 [ :LNOT: NewStyle_SpriteArea
        &       SpriteSpaceAddress,  SpriteSpaceMaxSize ; Sprite area (removable later)
 ]
 [ :LNOT: NewStyle_RAMDisc
        &       RAMDiscAddress,         RAMDiscMaxSize  ; RAM disc (removable later)
 ]
        &       PhysSpace,              512*1024*1024   ; PhysSpace
        &       &FF800000,              &007FFFFF       ; Shadow ROM (length has been bodged to avoid wrap problems)
        &       -1,                     0               ; termination

;**************************************************************************
;
;       AllocateAreaAddress - Find an area of logical space to use for this area
;
;       Internal routine called by DynArea_Create
;
; in:   r4 = area flags (NB if doubly mapped, we have to find space for both halves)
;       r5 = size (of each half in doubly mapped areas)
;
; out:  If successfully found an address, then
;         r0 preserved
;         r3 = logical address
;         V=0
;       else
;         r0 -> error
;         r3 preserved
;         V=1
;       endif

AllocateAreaAddress ENTRY "r0-r2,r4-r7"
        TST     r4, #DynAreaFlags_DoublyMapped          ; check if doubly mapped
        BEQ     %FT05                                   ; [not, so don't mangle]
        MOVS    r5, r5, LSL #1                          ; double size
        BCS     %FT90                                   ; if that wrapped then that's bad
05
        LDR     r3, =DynArea_NewAreasBase               ; r3 is our current attempt
        ADR     r0, FixedAreasTable                     ; r0 is ptr into fixed areas table
        MOV     r1, #DAList                             ; r1 is ptr into dyn areas list
10
        ADDS    r7, r3, r5                              ; r7 is our end+1
        BHI     %FT90                                   ; if we wrapped (but not end+1=0) then we failed
        BL      GetNextRange                            ; get next range from either list (r2=start, r6=end+1)
        CMP     r7, r2                                  ; if end(ours) <= start(next) then this is OK
        BLS     %FT80                                   ; (note this also works when r2=-1)
        CMP     r3, r6                                  ; else if start(ours) >= end(next)
        BCS     %BT10                                   ; then get another
        MOV     r3, r6                                  ; else make start(ours) := end(next)
        B       %BT10                                   ; and go back for another try

; we've succeeded - just apply unbodge for doubly-mapped areas

80
        TST     r4, #DynAreaFlags_DoublyMapped          ; if doubly mapped
        MOVNE   r5, r5, LSR #1                          ; halve size again
        ADDNE   r3, r3, r5                              ; and advance base address to middle
        CLRV
        EXIT

90
        ADRL    r0, ErrorBlock_CantAllocateArea
  [ International
        BL      TranslateError
  ]
        STR     r0, [sp]
        SETV
        EXIT                                    ; say we can't do it

;**************************************************************************
;
;       GetNextRange - Get next lowest range from either fixed or dynamic list
;
;       Internal routine called by AllocateAreaAddress
;
; in:   r0 -> next entry in fixed list
;       r1!0 -> next entry in dyn list
;
; out:  r2 = next lowest area base (-1 if none)
;       r6 = end of that range (undefined if none)
;       Either r0 or r1 updated to next one (except when r2=-1 on exit)
;

GetNextRange ENTRY "r7,r8"
        LDMIA   r0, {r2, r6}                            ; load start, size from fixed list
        ADD     r6, r6, r2                              ; r6 = end+1

        ASSERT  DANode_Link = 0
        LDR     r7, [r1, #DANode_Link]                  ; get next from dyn
        TEQ     r7, #0                                  ; if none
        MOVEQ   r8, #-1                                 ; then use addr -1
        BEQ     %FT10

        LDR     r8, [r7, #DANode_Flags]                 ; more double trouble
        TST     r8, #DynAreaFlags_DoublyMapped
        LDR     r8, [r7, #DANode_Base]
        LDR     lr, [r7, #DANode_MaxSize]
        SUBNE   r8, r8, lr
        MOVNE   lr, lr, LSL #1
        ADD     lr, lr, r8                              ; now r8 = start addr, lr = end+1
10
        CMP     r8, r2                                  ; if dyn one is earlier
        MOVCC   r2, r8                                  ; then use dyn start
        MOVCC   r6, lr                                  ; and end
        MOVCC   r1, r7                                  ; and advance dyn ptr
        EXIT    CC                                      ; then exit
        CMP     r2, #-1                                 ; else if not at end of fixed
        ADDNE   r0, r0, #8                              ; then advance fixed ptr
        EXIT

;**************************************************************************
;
;       AllocateBackingLevel2 - Allocate L2 pages for an area
;
;       Internal routine called by DynArea_Create
;
; in:   r3 = base address (will be page aligned)
;       r4 = area flags (NB if doubly mapped, then have to allocate for both halves)
;       r5 = size (of each half in doubly mapped areas)
;
; out:  If successfully allocated pages, then
;         All registers preserved
;         V=0
;       else
;         r0 -> error
;         V=1
;       endif

AllocateBackingLevel2 ENTRY "r0-r8,r11"
        TST     r4, #DynAreaFlags_DoublyMapped          ; if doubly mapped
        SUBNE   r3, r3, r5                              ; then area starts further back
        MOVNE   r5, r5, LSL #1                          ; and is twice the size

; NB no need to do sanity checks on addresses here, they've already been checked

; now round address range to 4M boundaries

        ADD     r5, r5, r3                              ; r5 -> end
        MOV     r0, #1 :SHL: 22
        SUB     r0, r0, #1
        BIC     r8, r3, r0                              ; round start address down (+ save for later)
        ADD     r5, r5, r0
        BIC     r5, r5, r0                              ; but round end address up

; first go through existing L2PT working out how much we need

        LDR     r7, =L2PT
        ADD     r3, r7, r8, LSR #10                     ; r3 -> start of L2PT for area
        ADD     r5, r7, r5, LSR #10                     ; r5 -> end of L2PT for area +1

        ADD     r1, r7, r3, LSR #10                     ; r1 -> L2PT for r3
        ADD     r2, r7, r5, LSR #10                     ; r2 -> L2PT for r5

        TEQ     r1, r2                                  ; if no pages needed
        BEQ     %FT30

        MOV     r4, #0                                  ; number of backing pages needed
10
        LDR     r6, [r1], #4                            ; get L2PT entry for L2PT
        TST     r6, #3                                  ; EQ if translation fault
        ADDEQ   r4, r4, #1                              ; if not there then 1 more page needed
        TEQ     r1, r2
        BNE     %BT10

; if no pages needed, then exit

        TEQ     r4, #0
        BEQ     %FT30

; now we need to claim r4 pages from the free pool, if possible; return error if not

        MOV     r1, #0
        LDR     r6, [r1, #FreePoolDANode + DANode_Size]
        SUBS    r6, r6, r4, LSL #12                     ; reduce free pool size by that many pages
        BCS     %FT14                                   ; if enough, skip next bit

; not enough pages in free pool currently, so try to grow it by the required amount

        Push    "r0, r1"
        MOV     r0, #ChangeDyn_FreePool
        RSB     r1, r6, #0                              ; size change we want (+ve)
        SWI     XOS_ChangeDynamicArea
        Pull    "r0, r1"
        BVS     %FT90                                   ; didn't manage change, so report error

        MOV     r6, #0                                  ; will be no pages left in free pool after this
14
        STR     r6, [r1, #FreePoolDANode + DANode_Size] ; if possible then update size

; after that we need to zero all these pages out (=> cause translation fault for area initially)

        LDR     r0, [r1, #FreePoolDANode + DANode_Base] ; r0 -> base of free pool
        ADD     r0, r0, r6                              ; r0 -> first byte we're taking out of free pool
        ADD     r6, r0, r4, LSL #12                     ; r6 -> byte after last in free pool
        Push    r8                                      ; save original logical address
        MOV     r8, #0                                  ; 0 => translation fault (note r1 already zero)
        MOV     r11, #0
        MOV     lr, #0
15
        STMIA   r0!, {r1,r8,r11,lr}                     ; store data
        TEQ     r0, r6
        BNE     %BT15
        Pull    r8

; now r0 -> after end of free pool (log addr)

        LDR     lr, =L1PT
        ADD     r8, lr, r8, LSR #18                     ; point r8 at start of L1 we may be updating
        ADD     r1, r7, r3, LSR #10                     ; point r1 at L2PT for r3 again
        MOV     r11, #AP_L2PT                           ; access privs (+CB bits)
20
        LDR     r6, [r1], #4                            ; get L2PT entry again
        TST     r6, #3                                  ; if no fault
        BNE     %FT25                                   ; then skip

        SUB     r0, r0, #4096                           ; move free pointer back
        Push    "r2,r4,r5"
        BL      MoveCAMatR0toR3                         ; else move page from end of free pool to r3
        Pull    "r2,r4,r5"

; now update 4 words in L1PT (corresponding to 4M of address space which is covered by the 4K of L2)
; and point them at the physical page we've just allocated (r1!-4 will already hold physical address+bits now!)

        LDR     r6, [r1, #-4]                           ; r6 = physical address for L2 page + other L2 bits
        MOV     r6, r6, LSR #12                         ; r6 = phys.addr >> 12
        LDR     lr, =L1_Page + L1_U                     ; form other bits to put in L1
        ORR     lr, lr, r6, LSL #12                     ; complete L1 entry
        STR     lr, [r8, #0]                            ; store entry for 1st MB
        ADD     lr, lr, #1024                           ; advance L2 pointer
        STR     lr, [r8, #4]                            ; store entry for 2nd MB
        ADD     lr, lr, #1024                           ; advance L2 pointer
        STR     lr, [r8, #8]                            ; store entry for 3rd MB
        ADD     lr, lr, #1024                           ; advance L2 pointer
        STR     lr, [r8, #12]                           ; store entry for 4th MB
        ARM_flush_TLB r6                                ; junk TLB(s) (probably not needed)
25
        ADD     r3, r3, #4096                           ; advance L2PT logical address
        ADD     r8, r8, #16                             ; move onto L1 for next 4M

        TEQ     r1, r2
        BNE     %BT20
30
        CLRV
        EXIT

        LTORG

; Come here if not enough space in free pool to allocate level2

90
        ADRL    r0, ErrorBlock_CantAllocateLevel2
  [ International
        BL      TranslateError
  ]
        STR     r0, [sp]
        SETV
        EXIT

;**************************************************************************
;
;       InitDynamicAreas - Initialise nodes for dynamic areas
;
;       It only initialises free pool, appspace and sysheap nodes
;       The other areas are created properly, after the screen area has been created (improperly)
;
; in:   -
; out:  -
;

InitDynamicAreas ENTRY "r0-r8,r11"
        MOV     lr, #AppSpaceDANode
        ADR     r0, InitAppSpaceTable
        LDMIA   r0, {r0-r8}
        STMIA   lr, {r0-r8}

        MOV     lr, #FreePoolDANode
        ADR     r0, InitFreePoolTable
        LDMIA   r0, {r0-r8}                     ; copy initial data into node
        LDR     r5, [lr, #RAMLIMIT-FreePoolDANode] ; max size is RAMLIMIT
        STMIA   lr, {r0-r8}

 [ GetPagesFromFreePool

; We have to move all free pages (ie ones not occupied by the static pages) into the free pool
; The lowest numbered physical pages must be put in last, so that when ReadCMOSAndConfigure is
; called to put in the screen, it will get the pages starting at 0 (when the screen is created
; as a dynamic area, this limitation can be removed).

; The free pages consist of two chunks of pages, each of which having consecutive physical page
; numbers. We start at MaxCamEntry and move back until we hit the end of the statics (which are
; at the start of the 1st non-video-RAM chunk). We then separately do the video RAM.

        MOV     r11, r3                         ; r11 = PPL (inc CB) for free pool
        MOV     r3, r2                          ; r3 = base address of free pool, ie where to put stuff
        MOV     r5, #0                          ; r5 = amount of memory in free pool so far (and ptr to 0)
        LDR     r2, [r5, #MaxCamEntry]          ; r2 = 1st page to put in free pool
        LDR     r7, [r5, #VideoSize]            ; r7 = size of video RAM
        MOV     r7, r7, LSR #12                 ; r7 = page number of start of static chunk
        ASSERT  SoftCamMapSize = L2PTSize +4
        MOV     r0, #L2PTSize
        LDMIA   r0, {r0, r8}                    ; r0 = L2PTSize, r8 = SoftCamMapSize
        ADD     r8, r8, r0                      ; add sizes together
        ADD     r8, r8, #StaticPagesSize + UndStackSize ; + number of bytes used for other static bits
        ADD     r8, r7, r8, LSR #12             ; r8 = page number of 1st page in 1st chunk not used for statics
10
        CMP     r2, r8                          ; are we into statics already
        SUBCC   r2, r7, #1                      ; if so, then move to last page of video RAM
        MOVCC   r8, #0                          ; and move barrier so we never hit it again
        BL      BangCamUpdate
        ADD     r3, r3, #4096                   ; advance logical address
        ADD     r5, r5, #4096
        SUBS    r2, r2, #1                      ; decrement page number
        BCS     %BT10                           ; if we haven't gone negative, then loop

        MOV     lr, #FreePoolDANode             ; may be used below to update DAList head ptr
        STR     r5, [lr, #DANode_Size]          ; update size of free pool in node

; Now initialise the system heap by hand, so we can start creating dynamic areas

        LDR     r0, =SysHeapStart
        LDR     r1, =magic_heap_descriptor
        MOV     r2, #Nil
        MOV     r3, #hpdsize
        MOV     r4, #32*1024 - (SysHeapStart-SysHeapChunkAddress)
        STMIA   r0, {r1-r4}

        MOV     r0, #0                          ; initialise module list to empty
        STR     r0, [r0, #Module_List]
 ]
 [ NewStyle_SysHeap
        MOV     lr, #SysHeapDANode              ; initialise system heap node
        ADR     r0, InitSysHeapTable
        LDMIA   r0, {r0-r8}
        STMIA   lr, {r0-r8}
 ]
        MOV     r0, #0
        STR     lr, [r0, #DAList]               ; store pointer to 1st node on list (either free pool or sys heap)

 [ NewStyle_All
        STR     r0, [r0, #CDASemaphore]         ; clear CDASemaphore
 ]

        EXIT

InitFreePoolTable
        &       0                               ; link: no more nodes on list
        &       ChangeDyn_FreePool
        &       FreePoolAddress
        &       AP_FreePool
        &       0                               ; size will be updated later
        &       0                               ; max size is computed
        &       0                               ; no workspace needed
        &       0                               ; no handler needed
        &       FreePoolString                  ; title

InitSysHeapTable
        &       FreePoolDANode                  ; link -> free pool node, since FreePoolAddress > SysHeapStart
        &       ChangeDyn_SysHeap
        &       SysHeapStart
        &       AP_SysHeap
        &       32*1024-(SysHeapStart-SysHeapChunkAddress) ; size
        &       SysHeapMaxSize
        &       SysHeapStart                    ; workspace pointer -> base of heap
        &       DynAreaHandler_SysHeap          ; area handler
        &       SysHeapString                   ; title

InitAppSpaceTable
        &       0                               ; link: not on list
        &       ChangeDyn_AplSpace
        &       0                               ; base address
        &       AP_AppSpace
        &       0                               ; size will be set up later
        &       AplWorkMaxSize
        &       0                               ; no workspace needed
        &       0                               ; no handler needed
        &       AppSpaceString                  ; title

FreePoolString
        =       "Free pool", 0
AppSpaceString
        =       "Application space", 0
SysHeapString
        =       "System heap", 0
        ALIGN

 ]

 [ NewCDA2
  [ NewStyle_All
ChangeDynamicSWI ROUT
        Push    "r0, r2-r9, r10, lr"

; and drop thru to ...
  ]

;**************************************************************************
;
;       CheckForNewArea - Perform operation of OS_ChangeDynamicArea, if
;                         area is on new list
;
; in:   r0 = area number
;       r1 = size of change
;       stack: r0,r2-r9,r10,lr
;
; out:  If not on list, then return to old routine at IsOldArea
;       Else perform operation and exit ourselves
;

CheckForNewArea ROUT
        MOV     r10, #0                         ; check we're not in an IRQ
        LDR     r10, [r10, #IRQsema]
        TEQ     r10, #0
 [ NewStyle_All
        LDREQ   r10, [r10, #CDASemaphore]       ; now also check whether ChangeDynamicArea is already threaded
        TEQEQ   r10, #0
        BNE     failure_IRQgoing
        MOV     r10, #1
        STR     r10, [r10, #CDASemaphore-1]     ; store non-zero value in CDASemaphore, to indicate we're threaded
 |
        BNE     failure_IRQgoing
 ]

 [ DebugCDA2
        DLINE   "Entering OS_ChangeDynamicArea (new code)"
 ]

        Push    "r1"
        MOV     r1, r0
 [ DebugCDA2
        DREG    r1, "Checking list for area number "
 ]
        BL      CheckAreaNumber                 ; check area number is on list
        Pull    "r1"
 [ NewStyle_All
        BCC     failure_IRQgoingClearSemaphore
 |
        BCC     IsOldArea                       ; if not, then use old code
 ]

 [ DebugCDA2
        DLINE   "Found entry on list"
 ]

        MOV     r5, #0
        LDR     r5, [r5, #Page_Size]            ; r5 = page size throughout
        SUB     r12, r5, #1                     ; r12 = page mask
        ADD     r1, r1, r12
        BICS    r1, r1, r12
        BEQ     IssueServiceMemoryMoved         ; zero pages! (r0 = area number, r1 = size change (0))
        BPL     AreaGrow

AreaShrink
        RSB     r1, r1, #0                      ; make size change positive
 [ DebugCDA2
        DREG    r0, "Shrinking area ", cc
        DREG    r1, " by "
 ]
        MOV     r11, r10                        ; source is area
        CMP     r0, #ChangeDyn_FreePool         ; if source is free pool
        ADREQ   r12, AppSpaceDANode             ; then dest is appspace
        ADRNE   r12, FreePoolDANode             ; else dest is free pool

        ASSERT  DANode_MaxSize = DANode_Size +4
        ADD     r2, r12, #DANode_Size
        LDMIA   r2, {r2, r3}
        SUB     lr, r3, r2                      ; lr = amount dest could grow

        LDR     r2, [r11, #DANode_Size]         ; amount src could shrink
        CMP     r2, lr
        MOVCC   lr, r2                          ; lr = min(amount dest could grow, amount src could shrink)

        CMP     r1, lr
        BLS     %FT15

; we can't move all that is required, so move smaller amount

        MOV     r1, lr                          ; move smaller amount
        BL      GenNotAllMovedError
        SUB     lr, r5, #1                      ; lr = pagesize mask
        BICS    r1, r1, lr                      ; a pagesize multiple
        BEQ     IssueServiceMemoryMoved
15
        CMP     r11, #AppSpaceDANode            ; if src <> appspace
        CMPNE   r12, #AppSpaceDANode            ; and dst <> appspace
        BNE     %FT17                           ; then don't call app
        Push    "r10"                           ; save -> to area we tried to shrink
        MOV     r10, r1
        BL      CheckAppSpace
        Pull    "r10"
        BVS     ChangeDynError
17
        BL      CallPreShrink
        BVS     ChangeDynError                  ; (r10 still points to area we tried to shrink)
        CMP     r2, r1                          ; can we move as much as we wanted?
        MOVCS   r2, r1                          ; if not, then move lesser amount (r2 = amount we're moving)
        BLCC    GenNotAllMovedError             ; store error, but continue

        TEQ     r2, #0                          ; if can't move any pages
        BEQ     NoMemoryMoved                   ; then exit, issuing Service_MemoryMoved

; Now move pages starting from end of area

        LDR     r0, [r11, #DANode_Base]
        LDR     r3, [r11, #DANode_Size]
        LDR     r6, [r11, #DANode_Flags]        ; r6 = src flags
        Push    "r3, r6"                        ; save src old size, src flags for later
        TST     r6, #DynAreaFlags_DoublyMapped  ; if src is doubly mapped
        MOVNE   r9, r3                          ; then set up offset from 1st copy to 2nd copy = old src size
        ADD     r0, r0, r3                      ; move r0 to point to after end of area (2nd copy)
        SUB     r3, r3, r2
        STR     r3, [r11, #DANode_Size]         ; store reduced source size

        LDR     r1, [r12, #DANode_Base]         ; this is free pool or app space, so it can't be doubly mapped!
        LDR     r3, [r12, #DANode_Size]
        ADD     r1, r1, r3                      ; r1 -> address of 1st extra page

        MOV     r4, r2
        LDR     r6, [r12, #DANode_Flags]        ; r6 = dst flags
        AND     r6, r6, #DynAreaFlags_AccessMask
20
        SUB     r0, r0, r5                      ; pre-decrement source pointer
 [ DebugCDA2
        DREG    r0, "Moving page at ", cc
        DREG    r1, " to ", cc
        DREG    r6, " with PPL "
 ]
        BL      MovePageAtR0ToR1WithAccessR6
        ADD     r1, r1, r5
        SUBS    r4, r4, r5
        BNE     %BT20

        ADD     r3, r3, r2
        STR     r3, [r12, #DANode_Size]         ; store increased destination size
        EORS    lr, r12, #AppSpaceDANode        ; check if dest = appspace (if so lr:=0)
        STREQ   r3, [lr, #MemLimit]             ; update memlimit if so

        Pull    "r3, r6"                        ; restore src old size, src flags
        TST     r6, #DynAreaFlags_DoublyMapped  ; if src doubly mapped
        SUBNES  r4, r3, r2                      ; then set r4 = number of pages to shuffle up
        BEQ     %FT30                           ; [not doubly mapped, or no pages left, so skip]

        SUB     r0, r0, r3                      ; move r0 back to end of 1st copy of pages remaining
        ADD     r1, r0, r2                      ; r1 is end of where they're moving to (should be src base address!)
 [ 1 = 1
 |
        AND     r6, r6, #DynAreaFlags_AccessMask
 ]
        MOV     r9, #0                          ; no funny stuff while moving these pages
25
        SUB     r0, r0, r5
        SUB     r1, r1, r5
 [ 1 = 1
        BL      GetPageFlagsForR0IntoR6
 ]
        BL      MovePageAtR0ToR1WithAccessR6
        SUBS    r4, r4, r5
        BNE     %BT25

30
        BL      CallPostShrink
        RSB     r1, r2, #0
        LDR     r0, [r11, #DANode_Number]       ; reload dynamic area number
        B       IssueServiceMemoryMoved

AreaGrow
 [ DebugCDA2
        DREG    r0, "Growing area ", cc
        DREG    r1, " by "
 ]
        MOV     r12, r10                        ; dest is area specified
        CMP     r0, #ChangeDyn_FreePool         ; if dest is free pool
        ADREQ   r11, AppSpaceDANode             ; then src is appspace
        ADRNE   r11, FreePoolDANode             ; else src is free pool (may later be free+apl)

        ASSERT  DANode_MaxSize = DANode_Size +4
        ADD     r2, r12, #DANode_Size
        LDMIA   r2, {r2, r3}
        SUB     lr, r3, r2                      ; lr = amount dest could grow

 [ DebugCDA2
        DREG    lr, "Dest could grow by "
 ]

        LDR     r2, [r11, #DANode_Size]         ; amount src could shrink
        CMP     r11, #AppSpaceDANode            ; if appspace
        SUBEQ   r2, r2, #&8000                  ; then can't take away last 32K (0..&7FFF)

 [ DebugCDA2
        DREG    r2, "Src could shrink by "
 ]

        CMP     r1, lr                          ; if enough room in dest
        CMPLS   r1, r2                          ; and enough space in src
        MOVLS   r3, r1                          ; then can do full amount
        BLS     %FT65                           ; so skip this bit

; we can't move all that is required
;
; if src = AplSpace then
;       (dest must be free pool)
;       move reduced amount
; else
;       (src must be free pool)
;       (dest <> AplSpace, cos that's a shrink!)
;       so check if adding aplspace would allow us to succeed
;       if it does then adjust registers, else give error
; endif
;

 [ DebugCDA2
        DLINE   "Can't move all required using just free pool"
 ]

        CMP     r11, #AppSpaceDANode
        BNE     %FT62
        MOV     r1, lr
        CMP     r1, r2
        MOVHI   r1, r2                          ; move min(max addable to dest, max removable from src)

 [ DebugCDA2
        DREG    r1, "Dest is free pool, moving reduced amount of "
 ]

61
        BL      GenNotAllMovedError
        SUB     lr, r5, #1                      ; lr = pagesize mask
        BICS    r1, r1, lr                      ; a pagesize multiple
        BEQ     IssueServiceMemoryMoved
        MOV     r3, r1
        B       %FT65

62
        MOV     r4, #AppSpaceDANode
        LDR     r6, [r4, #DANode_Size]          ; get current size of apl space
        SUB     r6, r6, #&8000                  ; can't take away 0-&7FFF
        ADD     r3, r2, r6                      ; add on to amount we could remove from free pool

 [ DebugCDA2
        DREG    r6, "Can get from app space an additional ", cc
        DREG    r3, " making a total of "
 ]

        CMP     r1, lr                          ; if not enough room in dest
        CMPLS   r1, r3                          ; or src still doesn't have enough
        MOVHI   r1, #0                          ; then don't move any
        BHI     %BT61                           ; and return error

        MOV     r3, r1                          ; amount actually doing

        TEQ     r2, #0                          ; else check to see if there was any at all in free pool
        MOVEQ   r11, #AppSpaceDANode            ; if not, then just take from aplspace
        MOVEQ   r7, r3                          ; and do all

        MOVNE   r11, #0                         ; else make src indicator reflect that we need both
        MOVNE   r7, r2                          ; but save amount we are taking from freepool

65

        Push    "r10"
        MOV     r10, #0                         ; default value if apl space not involved
        CMP     r11, #AppSpaceDANode            ; if source = aplspace
        RSBEQ   r10, r3, #0                     ; then make amount -ve
        CMP     r11, #0                         ; if source = free and apl
        SUBEQ   r10, r7, r3                     ; then make it -(amount removing from apl space)
        MOVNE   r7, r3                          ; else set up r7 to be total amount (wasn't set up above)

 [ DebugCDA2
        DREG    r3, "Amount actually moving into area = "
        DREG    r7, "Amount coming from 1st src area = "
 ]

        CMP     r10, #0                         ; if neither of the above then don't talk to app (CMP clears V)
        BLNE    CheckAppSpace                   ; else check app agrees
        Pull    "r10"
        BVS     ChangeDynError

; now split up grow into bite-size chunks, and call DoTheGrow to do each one

        Push    "r3"                            ; save original total amount
        TEQ     r11, #0                         ; if taking from both free + apl
        MOVEQ   r11, #FreePoolDANode            ; then start with free
 [ DAF_SpecifyBit
        LDR     lr, [r12, #DANode_Flags]        ; could this area require particular physical pages at all?
        TST     lr, #DynAreaFlags_NeedsSpecificPages
        BNE     %FT70                           ; [yes it could, so do it in lumps]

        MOV     r1, #0                          ; no page block
        MOV     r2, r3, LSR #12                 ; number of pages to do
        BL      CallPreGrow
        LDRVS   r3, [sp]                        ; if error, haven't done any, so restore total as how much to do
        BVS     %FT95

        Push    "r3, r7"
        MOV     r2, r7, LSR #12
        BL      DoTheGrowNotSpecified
        Pull    "r3, r7"
        SUBS    r3, r3, r7                      ; subtract off what we just did

        MOVHI   r7, r3                          ; if not finished, then start 2nd half
        MOVHI   r11, #AppSpaceDANode            ; which is app space
        MOVHI   r2, r7, LSR #12
        BLHI    DoTheGrowNotSpecified

        LDR     r3, [sp]                        ; restore total amount
        MOV     r1, #0                          ; indicate no page block (and ptr to semaphore)
        STR     r1, [r1, #CDASemaphore]         ; OK to reenter now (we've done the damage)
        MOV     r2, r3, LSR #12
        BL      CallPostGrow
        BVS     %FT95
        B       %FT80
 ]

70
        Push    "r3, r7"
        CMP     r7, #PageBlockChunk             ; only do 1 area, so do min(r7,page)
        MOVHI   r7, #PageBlockChunk
        MOV     r2, r7, LSR #12                 ; number of entries to fill in in page block
        BL      DoTheGrow
        Pull    "r3, r7"
        BVS     %FT95
        CMP     r7, #PageBlockChunk             ; if 1st area is more than 1 page
        SUBHI   r3, r3, #PageBlockChunk         ; then reduce total
        SUBHI   r7, r7, #PageBlockChunk         ; and partial amounts by 1 page and do it again
        BHI     %BT70

        SUBS    r3, r3, r7                      ; subtract off what we just did
        MOVHI   r7, r3                          ; if not finished, then start 2nd half
        MOVHI   r11, #AppSpaceDANode            ; which is app space
        BHI     %BT70                           ; and loop
80
        Pull    "r3"                            ; restore total amount

        MOV     r1, r3
        LDR     r0, [r12, #DANode_Number]       ; reload dynamic area number
        B       IssueServiceMemoryMoved

95
        Pull    "r1"                            ; restore total amount
        SUB     r1, r1, r3                      ; subtract off amount left, to leave done amount
        B       ChangeDynErrorSomeMoved

GenNotAllMovedError ENTRY "r0"
        ADRL    r0, ErrorBlock_ChDynamNotAllMoved
 [ International
        BL      TranslateError
 ]
        STR     r0, [sp, #2*4]          ; sp -> r0,lr, then stacked r0,r2-r9,r10,lr
        LDR     lr, [sp, #12*4]
        ORR     lr, lr, #V_bit
        STR     lr, [sp, #12*4]
        EXIT

ChangeDynError

; in:   r0 -> error
;       r10 -> area that we tried to shrink/grow

        MOV     r1, #0
ChangeDynErrorSomeMoved
        STR     r0, [sp]
        LDR     lr, [sp, #10*4]
        ORR     lr, lr, #V_bit
        STR     lr, [sp, #10*4]
        B       SomeMemoryMoved

NoMemoryMoved
        MOV     r1, #0                          ; nothing moved
SomeMemoryMoved
        LDR     r0, [r10, #DANode_Number]       ; reload area number

; and drop thru to...

IssueServiceMemoryMoved

; in:   r0 = area number that was shrunk/grown
;       r1 = amount moved (signed)
;
        Push    "r1"
        MOV     r2, r0                  ; r2 = area number
        MOV     r0, r1                  ; amount moved (signed)
        MOV     r1, #Service_MemoryMoved
        BL      Issue_Service
        Pull    "r1"                    ; restore amount moved
        TEQ     r1, #0
        RSBMI   r1, r1, #0              ; r1 on exit = unsigned amount

 [ NewStyle_All
        MOV     r0, #0
        STR     r0, [r0, #CDASemaphore] ; clear CDASemaphore
 ]
        Pull    "r0, r2-r9, r10, lr"
        ExitSWIHandler

; ***********************************************************************************
;
;       DoTheGrow - Do one chunk of growing, small enough to fit into the page block on the stack
;
; in:   r2 = number of entries to put in page block (for this chunk)
;       r5 = page size
;       r7 = amount taking from src area (in this chunk)
;       (r10 -> dest area)
;       r11 -> src area
;       r12 -> dest area
;
; out:  r0-r2,r4,r6-r9 may be corrupted
;       r3,r5,r10-r12 preserved
;
; Note: Removal is from one area only, the calling routine breaks the chunks up at free/app boundary.

; Temporary (stack frame) workspace used by this routine

                ^       0, sp
NumEntries      #       4                       ; Number of entries to do for this chunk
DestAddr        #       4                       ; Log addr of 1st page being added to dest
DestFlags       #       4                       ; Page flags for destination area
TotalAmount     #       4                       ; Total size of grow for this chunk (ie entry value of r3)
SavedPSR        #       4                       ; PC+PSR before IRQs disabled
Offset1To2      #       4                       ; Offset from 1st to 2nd bank

 [ DAF_SpecifyBit
DoTheGrowNotSpecifiedStackSize * :INDEX: @      ; amount of stack needed for 'not specified' version
 ]

PageBlock1      #       PageBlockSize           ; 1st page block, for original page numbers and phys. addrs
PageBlock2      #       PageBlockSize           ; 2nd page block, for new page numbers and phys. addrs

DoTheGrowStackSize *    :INDEX: @

DoTheGrow ENTRY "r3,r5,r10-r12", DoTheGrowStackSize

; First fill in the page block with -1 in the physical page number words

        STR     r2, NumEntries                  ; save number of entries for use later
        STR     r7, TotalAmount                 ; save amount growing by

        ADR     r1, PageBlock1                  ; point at 1st page block on stack
        ADD     lr, r2, r2, LSL #1              ; lr = number of words in page block
        ADD     lr, r1, lr, LSL #2              ; lr -> off end of page block
        MOV     r0, #-1
10
        STR     r0, [lr, #-12]!                 ; store -1, going backwards
        STR     r0, [lr, #PageBlockSize]        ; and put -1 in 2nd page block as well
        TEQ     lr, r1                          ; until the end
        BNE     %BT10

; Now call the pre-grow handler

        MOV     r3, r7
        BL      CallPreGrow
        EXIT    VS

; now check to see if particular pages are required

        LDR     lr, [r1]                        ; load page number in 1st entry
        CMP     lr, #-1                         ; is it -1?
        BNE     DoTheGrowPagesSpecified         ; if not, then jump to special code

; now move pages starting from end of area

        MOV     r2, r3                          ; amount moving
        LDR     r0, [r11, #DANode_Base]
        LDR     r3, [r11, #DANode_Size]
        ADD     r0, r0, r3                      ; move r0 to point to after end of area
        SUB     r3, r3, r2                      ; reduce by amount moving from area
        STR     r3, [r11, #DANode_Size]         ; store reduced source size
        TEQ     r11, #AppSpaceDANode                    ; if just appspace
        STREQ   r3, [r11, #MemLimit-AppSpaceDANode]     ; then store in memlimit

        LDR     r1, [r12, #DANode_Base]
        LDR     r3, [r12, #DANode_Size]

        LDR     r6, [r12, #DANode_Flags]        ; r6 = dst flags
        AND     r6, r6, #DynAreaFlags_AccessMask
        TST     r6, #DynAreaFlags_DoublyMapped  ; check if dst is doubly mapped
        BEQ     %FT25                           ; [it's not, so skip all this]

; we must shunt all existing pages in dest area down

        MOVS    r4, r3                          ; amount to do
        BEQ     %FT20                           ; [none, so skip all this]
        Push    "r0, r1"
        SUB     r0, r1, r3                      ; src starts at start of 1st copy = start of 2nd - old size
        SUB     r1, r0, r2                      ; dst start = src start - amount of room needed
        MOV     r9, #0                          ; no funny business while moving these pages
15
        BL      MovePageAtR0ToR1WithAccessR6    ; move page
        ADD     r0, r0, r5                      ; advance src ptr
        ADD     r1, r1, r5                      ; advance dst ptr
        SUBS    r4, r4, r5                      ; one less page to move
        BNE     %BT15                           ; loop if more
        Pull    "r0, r1"                        ; restore original regs
20
        ADD     r9, r3, r2                      ; set up offset from 1st copy to 2nd copy (= new size)
25
        ADD     r1, r1, r3                      ; r1 -> address of 1st extra page
        MOV     r4, #0                          ; amount done so far
        MOV     r10, r2                         ; move amount to do into r10, as routine returns page number in r2
        ADR     r3, PageBlock1                  ; point at 1st entry we have to update
30
        SUB     r0, r0, r5                      ; pre-decrement source pointer
 [ DebugCDA2
        DREG    r0, "Moving page at ", cc
        DREG    r1, " to ", cc
        DREG    r6, " with PPL "
 ]
        BL      MovePageAtR0ToR1WithAccessR6ReturnPageNumber
        STR     r2, [r3], #12                   ; store page number and move on
        ADD     r1, r1, r5
        ADD     r4, r4, r5
        CMP     r4, r10                         ; have we done all of it?
        BNE     %BT30                           ; [no, so loop]
35
        LDR     r3, [r12, #DANode_Size]
        ADD     r3, r3, r10
        STR     r3, [r12, #DANode_Size]         ; store increased destination size

        MOV     r3, r10                         ; r3 = size of change
        LDR     r2, NumEntries                  ; restore number of entries in page block
        ADR     r1, PageBlock1                  ; point at page block 1 with page numbers filled in
        BL      CallPostGrow
        CLRV
        EXIT

37

; Come here if a required page is not available
; First we need to go back thru all the part of the page block we've already done,
; marking the pages as not being used after all

        ADR     r2, PageBlock1
38
        LDR     r4, [r1, #-12]!                 ; r4 = physical page number
        ADD     r4, r0, r4, LSL #3              ; point at cam entry
        LDMIA   r4, {r8, lr}
        BIC     lr, lr, #PageFlags_Required
        STMIA   r4, {r8, lr}
        TEQ     r1, r2
        BNE     %BT38

; since pre-grow handler exited without an error, we have to keep our promise
; to call the post-grow handler

        MOV     r3, #0                          ; no pages moved
        MOV     r2, #0                          ; no pages moved
        ADR     r1, PageBlock1                  ; not really relevant
        BL      CallPostGrow

        ADR     r0, ErrorBlock_CantGetPhysMem
 [ International
        BL      TranslateError
 ]
        SETV
        EXIT

        MakeErrorBlock  CantGetPhysMem

DoTheGrowPagesSpecified

; First check if any of the pages requested are unavailable
; At the same time as we're doing this, we fill in the log. and phys. addresses in the block

        MOV     r0, #0
        LDR     r0, [r0, #CamEntriesPointer]
        LDR     r6, =L2PT
40
        LDR     r3, [r1], #12                   ; r4 = physical page number
        ADD     r4, r0, r3, LSL #3              ; point at cam entry
        LDMIA   r4, {r8, lr}                    ; r8 = log. addr, lr = PPL
        STR     r8, [r1, #4-12]                 ; store log. addr in page block
        STR     r8, [r1, #PageBlockSize+4-12]   ; and in 2nd page block

        TST     lr, #PageFlags_Unavailable :OR: PageFlags_Required ; if page in use by someone else, or by us, then return error
        BNE     %BT37
        ORR     lr, lr, #PageFlags_Required     ; set bit in flags to say page will be needed
        STR     lr, [r4, #4]                    ; and store back

; work out physical address direct from physical page number, NOT from logical address, since log addr may be 01F08000 (multiply mapped)

        MOV     r4, #PhysRamTable
42
        LDMIA   r4!, {r8, lr}                   ; load phys addr, size
        SUBS    r3, r3, lr, LSR #12             ; subtract off number of pages in this chunk
        BCS     %BT42

        ADD     r3, r3, lr, LSR #12             ; put back what could not be subtracted
        ADD     r8, r8, r3, LSL #12             ; and add onto base address
        STR     r8, [r1, #8-12]                 ; store physical address in page block

        SUBS    r2, r2, #1
        BNE     %BT40

; now issue Service_PagesUnsafe

        ADR     r2, PageBlock1                  ; r2 -> 1st page block
        LDR     r3, NumEntries                  ; r3 = number of entries in page block
        MOV     r1, #Service_PagesUnsafe
        BL      Issue_Service

  [ StrongARM
    ;
    ;Ahem! The data is moved to new pages by reading old pages via 'physical address' (flat copy of
    ;      physical space at virtual addr. 2G). This means data read may not be up to date wrt data in
    ;      StrongARM's write-back cache, and is a potential cache incoherency anyway (two virtual mappings
    ;      to one physical).
    ;      So, clean/flush StrongARM data cache wrt to pages first. Incidentally, since StrongARM does
    ;      not support burst read LDMs from uncacheable areas, the read is going to be a little slow anyway).
    ;
    ;
    ARM_number r0
    CMP     r0,#&A
    BLEQ    dtgps_SAcleanflush
  ]

  [ ARM810support
    ;
    ; ARM810 has writeback cache too
    ;
    ARM_number r0
    CMP     r0,#8
    BLEQ    dtgps_810cleanflush
  ]

; now move the pages

        LDR     r2, TotalAmount                 ; amount moving
        LDR     r0, [r11, #DANode_Base]
        LDR     r3, [r11, #DANode_Size]
        ADD     r0, r0, r3                      ; move r0 to point to after end of area
        SUB     r3, r3, r2                      ; reduce by amount moving from area
        STR     r3, [r11, #DANode_Size]         ; store reduced source size
        TEQ     r11, #AppSpaceDANode                    ; if appspace
        STREQ   r3, [r11, #MemLimit-AppSpaceDANode]     ; then update memlimit

        LDR     r1, [r12, #DANode_Base]
        LDR     r3, [r12, #DANode_Size]

        LDR     r6, [r12, #DANode_Flags]        ; r6 = dst flags
        AND     r6, r6, #DynAreaFlags_AccessMask
        ORR     r6, r6, #PageFlags_Unavailable  ; set unavailable bit
        STR     r6, DestFlags                   ; save for later
        TST     r6, #DynAreaFlags_DoublyMapped  ; check if dst is doubly mapped
        BEQ     %FT55                           ; [it's not, so skip all this, and r9 will be irrelevant]

; we must shunt all existing pages in dest area down

        MOVS    r4, r3                          ; amount to do
        BEQ     %FT50                           ; [none, so skip all this]
        Push    "r0, r1"
        SUB     r0, r1, r3                      ; src starts at start of 1st copy = start of 2nd - old size
        SUB     r1, r0, r2                      ; dst start = src start - amount of room needed
        MOV     r9, #0                          ; no funny business while moving these pages
45
        BL      MovePageAtR0ToR1WithAccessR6    ; move page
        ADD     r0, r0, r5                      ; advance src ptr
        ADD     r1, r1, r5                      ; advance dst ptr
        SUBS    r4, r4, r5                      ; one less page to move
        BNE     %BT45                           ; loop if more
        Pull    "r0, r1"                        ; restore original regs
50
        ADD     r9, r3, r2                      ; set up offset from 1st copy to 2nd copy (= new size)
55
        STR     r9, Offset1To2                  ; store offset 1st to 2nd copy
        ADD     r1, r1, r3                      ; r1 -> address of 1st extra page
        STR     r1, DestAddr
        ADR     r8, PageBlock1                  ; r8 -> position in 1st page block
        SUB     r2, r0, r2                      ; r2 = lowest address being removed from src
        MOV     r3, #0
        LDR     r3, [r3, #CamEntriesPointer]
        MOV     r4, r0                          ; r4 is where we're at in allocating spare logical addresses
        LDR     r9, NumEntries                  ; number of entries still to do in 1st loop

; Now before we start, we must construct the second page block, with replacement page numbers

;        DLINE   "Start of 1st loop"

60
        LDR     r6, [r8], #12                   ; r6 = page number required
        LDR     r10, [r8, #8-12]                ; r10 = phys addr
        LDR     lr, [r3, r6, LSL #3]            ; lr = logical address for this page

;        DREG    r6, "Checking page ", cc
;        DREG    lr, "at address "

        CMP     lr, r2                          ; check if address is one being taken from src anyway
        BCC     %FT63
        CMP     lr, r0
        BCS     %FT63

;        DLINE   "Page is being taken away anyway"
        B       %FT68                           ; [page is being taken anyway, so use same page number + phys addr in 2nd block]

; page is not one being taken away, so put in 1st replacement page that isn't required by area

63
;        DLINE   "Page is not being taken, looking for replacement"

64
        SUB     r4, r4, r5                      ; go onto next page being taken from src
;        DREG    r4, "Considering address "

        LDR     lr, =L2PT
        LDR     lr, [lr, r4, LSR #10]           ; get L2PT entry (to get phys addr) for next free page
        MOV     r10, lr, LSR #12                ; r10 = phys addr >>> 12

; now convert phys addr to page number

        MOV     r6, #0
        MOV     r1, #PhysRamTable
66
        LDMIA   r1!, {r7, lr}                   ; load phys addr, size
        SUB     r7, r10, r7, LSR #12            ; number of pages into this bank
        CMP     r7, lr, LSR #12                 ; if more than there are here,
        ADDCS   r6, r6, lr, LSR #12             ; then advance page number by number of pages in this bank
        BCS     %BT66                           ; and go onto next bank

        ADD     r6, r6, r7                      ; advance page number by no. of pages into this bank

        ADD     r1, r3, r6, LSL #3              ; r1 -> cam entry for this page
        LDR     r1, [r1, #4]                    ; get PPL for this page
        TST     r1, #PageFlags_Required         ; if this page is required for the operation
        BNE     %BT64                           ; then try next page

        MOV     r10, r10, LSL #12               ; make r10 proper phys addr
;        DREG    r6, "Using page number "
68
        STR     r6, [r8, #PageBlockSize-12]     ; store page number in 2nd block
        STR     r10, [r8, #PageBlockSize+8-12]  ; and store phys addr

        SUBS    r9, r9, #1                      ; one less entry to do
        BNE     %BT60

        MOV     r7, r3                          ; r7 -> camentries

; Now we can go onto the 2nd loop which actually moves the pages

        LDR     r1, DestAddr
        MOV     r4, #0                          ; amount done
        MOV     r0, r7                          ; point r0 at camentries
        LDR     r7, TotalAmount                 ; amount to do
        ADR     r8, PageBlock1
        LDR     r9, Offset1To2
70
        STR     pc, SavedPSR                    ; save old PSR (note: stack must be flat when we do this!)

        Push    "r0-r4,r7-r12"                  ; save regs used during copy
        MOV     r1, #Service_ClaimFIQ
        BL      Issue_Service

        TEQP    pc, #SVC_mode + I_bit           ; disable IRQs round here
        NOP

        LDR     r6, [r8, #0]                    ; r6 = page number required
        LDR     lr, [r8, #PageBlockSize+0]      ; lr = page number of replacement page
        TEQ     r6, lr                          ; if the same
        Pull    "r0-r4,r7-r12", EQ              ; then restore registers
        BEQ     %FT76                           ; and skip copy and first page move

        LDR     r0, [r0, lr, LSL #3]            ; r0 = log. address for replacement page (NB use logical address to write to, for cache consistency)
        LDR     r6, [r8, #8]                    ; r6 = physical address of src for copy
        ORR     r6, r6, #PhysSpace              ; must use physical address, as page may be mapped to 01F08000 along with others
        ADD     lr, r6, r5                      ; lr = end src address
72
        LDMIA   r6!, {r2, r3, r4, r7, r9, r10, r11, r12}
        STMIA   r0!, {r2, r3, r4, r7, r9, r10, r11, r12}
        TEQ     r6, lr
        BNE     %BT72

; now check if page we're replacing is in L2PT, and if so then adjust L1PT entries (4 of these)

        LDR     r6, [r8, #4]                    ; look at logical address of page being replaced
        SUBS    r6, r6, #L2PT
        BCC     %FT74                           ; address is below L2PT
        CMP     r6, #4*1024*1024
        BCS     %FT74                           ; address is above L2PT

        LDR     r2, =L1PT
        ADD     r2, r2, r6, LSR #(12-4)         ; address in L1 of 4 consecutive words to update
        LDR     r3, [r2]                        ; load 1st word, to get AP etc bits
        MOV     r3, r3, LSL #(31-9)             ; junk other bits
        LDR     r4, [r8, #PageBlockSize+8]      ; load new physical address for page
        ORR     r3, r4, r3, LSR #(31-9)         ; and merge with AP etc bits
        STR     r3, [r2], #4
        ADD     r3, r3, #&400
        STR     r3, [r2], #4
        ADD     r3, r3, #&400
        STR     r3, [r2], #4
        ADD     r3, r3, #&400
        STR     r3, [r2], #4
74
        Pull    "r0-r4,r7-r12"                  ; restore registers

        MOV     lr, #0
        LDR     lr, [lr, #CamEntriesPointer]    ; lr -> soft cam map
        ADD     lr, lr, #4                      ; point at PPLs, not addresses
        LDR     r2, [r8, #0]                    ; need to get PPL for page being replaced
        LDR     r11, [lr, r2, LSL #3]
        BIC     r11, r11, #PageFlags_Required   ; knock off bits that indicate that it was a required page

        ADD     lr, r8, #PageBlockSize
        LDMIA   lr, {r2, r3}                    ; get page number, logical address
        BL      Call_CAM_Mapping                ; move replacement page in
76
        LDR     r2, [r8, #0]
        MOV     r3, r1
        LDR     r11, DestFlags
        BL      Call_CAM_Mapping                ; move needed page to destination

        LDR     lr, SavedPSR
        TEQP    lr, #0

        Push    "r1"
        MOV     r1, #Service_ReleaseFIQ
        BL      Issue_Service
        Pull    "r1"

        ADD     r1, r1, r5                      ; advance dest ptr
        ADD     r4, r4, r5                      ; increment amount done
        ADD     r8, r8, #12                     ; advance page block ptr
        CMP     r4, r7                          ; have we done all?
        BNE     %BT70                           ; [no, so loop]

        LDR     r3, [r12, #DANode_Size]
        ADD     r3, r3, r7
        STR     r3, [r12, #DANode_Size]         ; store increased destination size

; now issue Service_PagesSafe

        LDR     r2, NumEntries
        ADR     r3, PageBlock1
        ADR     r4, PageBlock2
        MOV     r1, #Service_PagesSafe
        BL      Issue_Service

; now call Post_Grow handler

        LDR     r3, TotalAmount                 ; size of grow
        LDR     r2, NumEntries                  ; restore number of entries in page block
        ADR     r1, PageBlock1                  ; point at page block 1 with page numbers filled in
        BL      CallPostGrow
        CLRV
        EXIT

 [ DAF_SpecifyBit
; ***********************************************************************************
;
;       DoTheGrowNotSpecified - Do one chunk of growing, with no page block
;                               But don't call pre-grow or post-grow either
;
; in:   r2 = number of pages to do (in this chunk)
;       r5 = page size
;       r7 = amount taking from src area (in this chunk)
;       (r10 -> dest area)
;       r11 -> src area
;       r12 -> dest area
;
; out:  r0-r2,r4,r6-r9 may be corrupted
;       r3,r5,r10-r12 preserved
;
; Note: Removal is from one area only, the calling routine breaks the chunk at free/app boundary.


DoTheGrowNotSpecified ENTRY "r3,r5,r10-r12", DoTheGrowNotSpecifiedStackSize

        STR     r2, NumEntries                  ; save number of entries for use later
        STR     r7, TotalAmount                 ; save amount growing by

; now move pages starting from end of area

        MOV     r2, r7                          ; amount moving
        LDR     r0, [r11, #DANode_Base]
        LDR     r3, [r11, #DANode_Size]
        ADD     r0, r0, r3                      ; move r0 to point to after end of area
        SUB     r3, r3, r2                      ; reduce by amount moving from area
        STR     r3, [r11, #DANode_Size]         ; store reduced source size
        TEQ     r11, #AppSpaceDANode                    ; if just appspace
        STREQ   r3, [r11, #MemLimit-AppSpaceDANode]     ; then store in memlimit

        LDR     r1, [r12, #DANode_Base]
        LDR     r3, [r12, #DANode_Size]

        LDR     r6, [r12, #DANode_Flags]        ; r6 = dst flags
        AND     r6, r6, #DynAreaFlags_AccessMask
        TST     r6, #DynAreaFlags_DoublyMapped  ; check if dst is doubly mapped
        BEQ     %FT25                           ; [it's not, so skip all this]

; we must shunt all existing pages in dest area down

        MOVS    r4, r3                          ; amount to do
        BEQ     %FT20                           ; [none, so skip all this]
        Push    "r0, r1"
        SUB     r0, r1, r3                      ; src starts at start of 1st copy = start of 2nd - old size
        SUB     r1, r0, r2                      ; dst start = src start - amount of room needed
        MOV     r9, #0                          ; no funny business while moving these pages
15
        BL      MovePageAtR0ToR1WithAccessR6    ; move page
        ADD     r0, r0, r5                      ; advance src ptr
        ADD     r1, r1, r5                      ; advance dst ptr
        SUBS    r4, r4, r5                      ; one less page to move
        BNE     %BT15                           ; loop if more
        Pull    "r0, r1"                        ; restore original regs
20
        ADD     r9, r3, r2                      ; set up offset from 1st copy to 2nd copy (= new size)
25
        ADD     r1, r1, r3                      ; r1 -> address of 1st extra page
        MOV     r4, #0                          ; amount done so far
        MOV     r10, r2                         ; move amount to do into r10
30
        SUB     r0, r0, r5                      ; pre-decrement source pointer
 [ DebugCDA2
        DREG    r0, "Moving page at ", cc
        DREG    r1, " to ", cc
        DREG    r6, " with PPL "
 ]
        BL      MovePageAtR0ToR1WithAccessR6
        ADD     r1, r1, r5
        ADD     r4, r4, r5
        CMP     r4, r10                         ; have we done all of it?
        BNE     %BT30                           ; [no, so loop]
35
        LDR     r3, [r12, #DANode_Size]
        ADD     r3, r3, r10
        STR     r3, [r12, #DANode_Size]         ; store increased destination size

        CLRV
        EXIT

 ] ; DAF_SpecifyBit

; ***********************************************************************************
;
;       CheckAppSpace - If appspace involved in transfer, issue Service or UpCall
;
;       Internal routine, called by OS_ChangeDynamicArea
;
; in:   r0 = area number passed in to ChangeDyn
;       r10 = size of change (signed)
;       r11 -> node for src
;       r12 -> node for dest
;
; out:  If appspace not involved, or application said it was OK, then
;         V=0
;         All registers preserved
;       else
;         V=1
;         r0 -> error
;         All other registers preserved
;       endif
;

CheckAppSpace ENTRY "r0-r3"
        MOV     r2, #0
        LDR     r3, [r2, #AplWorkSize]
        LDR     r2, [r2, #Curr_Active_Object]
        CMP     r2, r3                          ; check if CAO outside application space
        BHI     %FT20                           ; [it is so issue Service not UpCall]

; CAO in application space, so issue UpCall to check it's OK

        MOV     r0, #UpCall_MovingMemory :AND: &FF
        ORR     r0, r0, #UpCall_MovingMemory :AND: &FFFFFF00
        MOVS    r1, r10
        RSBMI   r1, r1, #0                      ; r1 passed in is always +ve (probably a bug, but should be compat.)

        SWI     XOS_UpCall
        CMP     r0, #UpCall_Claimed             ; if upcall claimed
        EXIT    EQ                              ; then OK to move memory, so exit (V=0 from CMP)

        ADR     r0, ErrorBlock_ChDynamCAO
10
 [ International
        BL      TranslateError
 ]
        STR     r0, [sp]
        SETV
        EXIT

; IF service call claimed Then Error AplWSpaceInUse

20
        MOV     r0, r10                         ; amount removing from aplspace
        MOV     r1, #Service_Memory
        BL      Issue_Service
        CMP     r1, #Service_Serviced
        ADREQ   r0, ErrorBlock_AplWSpaceInUse   ; if service claimed, then return error
        BEQ     %BT10
        CLRV                                    ; else OK
        EXIT

 ]
        MakeErrorBlock AplWSpaceInUse
        MakeErrorBlock ChDynamCAO
 [ NewCDA2

; ***********************************************************************************
;
;       CallPreShrink - Call pre-shrink routine
;
; in:   r1 = amount shrinking by (+ve)
;       r5 = page size
;       r11 -> node for area being shrunk
;
; out:  If handler exits VC, then r2 = no. of bytes area can shrink by
;       else r0 -> error block or 0 for generic error, and r2=0
;

CallPreShrink ENTRY "r0,r3,r4, r12"
        LDR     r0, [r11, #DANode_Handler]              ; check if no handler
        CMP     r0, #0                                  ; if none (V=0)
        EXIT    EQ                                      ; then exit

        MOV     r0, #DAHandler_PreShrink                ; r0 = reason code
        MOV     r3, r1                                  ; r3 = amount shrinking by
        LDR     r4, [r11, #DANode_Size]                 ; r4 = current size
        ASSERT  DANode_Handler = DANode_Workspace +4
        ADD     r12, r11, #DANode_Workspace
        MOV     lr, pc
        LDMIA   r12, {r12, pc}                          ; load workspace pointer and jump to handler

; shrink amount returned by handler may not be page multiple (according to spec),
; so we'd better make it so.

        SUB     lr, r5, #1
        BIC     r2, r3, lr                              ; make page multiple and move into r2
        EXIT    VC
        TEQ     r0, #0                                  ; if generic error returned
        ADREQL  r0, ErrorBlock_ChDynamNotAllMoved       ; then substitute real error message
 [ International
        BLEQ    TranslateError
 ]
        STR     r0, [sp]
        SETV
        EXIT

; ***********************************************************************************
;
;       CallPostShrink - Call post-shrink routine
;
; in:   r2 = amount shrinking by (+ve)
;       r5 = page size
;       r11 -> node for area being shrunk
;
; out:  All registers preserved
;

CallPostShrink ENTRY "r0,r3,r4, r12"
        LDR     r0, [r11, #DANode_Handler]              ; check if no handler
        CMP     r0, #0                                  ; if none (V=0)
        EXIT    EQ                                      ; then exit

        MOV     r0, #DAHandler_PostShrink               ; r0 = reason code
        MOV     r3, r2                                  ; r3 = amount shrunk by
        LDR     r4, [r11, #DANode_Size]                 ; r4 = new size
        ASSERT  DANode_Handler = DANode_Workspace +4
        ADD     r12, r11, #DANode_Workspace
        MOV     lr, pc
        LDMIA   r12, {r12, pc}                          ; load workspace pointer and jump to handler

        EXIT

; ***********************************************************************************
;
;       CallPreGrow - Call pre-grow routine
;
; in:   Eventually r1 -> page block (on stack)
;                  r2 = number of entries in block
;       but for now these are both undefined
;       r3 = amount area is growing by
;       r5 = page size
;       r12 -> node for area being grown
;
; out:  If can't grow, then
;         r0 -> error
;         V=1
;       else
;         page block may be updated with page numbers (but not yet!)
;         All registers preserved
;         V=0
;       endif
;

CallPreGrow ENTRY "r0,r4, r12"
        LDR     r0, [r12, #DANode_Handler]              ; check if no handler
        CMP     r0, #0                                  ; if none (V=0)
        EXIT    EQ                                      ; then exit

        MOV     r0, #DAHandler_PreGrow                  ; r0 = reason code
        LDR     r4, [r12, #DANode_Size]                 ; r4 = current size
        ASSERT  DANode_Handler = DANode_Workspace +4
        ADD     r12, r12, #DANode_Workspace
        MOV     lr, pc
        LDMIA   r12, {r12, pc}                          ; load workspace pointer and jump to handler
        EXIT    VC                                      ; if no error then exit

        TEQ     r0, #0                                  ; if generic error returned
        ADREQL  r0, ErrorBlock_ChDynamNotAllMoved       ; then substitute real error message
 [ International
        BLEQ    TranslateError
 ]
        STR     r0, [sp]
        SETV
        EXIT

; ***********************************************************************************
;
;       CallPostGrow - Call post-grow routine
;
; in:   Eventually, r1 -> page block with actual pages put in
;                   r2 = number of entries in block
;       r3 = size of change
;       r5 = page size
;       r12 -> node for area being grown
;
; out:  All registers preserved
;

CallPostGrow ENTRY "r0,r3,r4, r12"
        LDR     r0, [r12, #DANode_Handler]              ; check if no handler
        CMP     r0, #0                                  ; if none (V=0)
        EXIT    EQ                                      ; then exit

        MOV     r0, #DAHandler_PostGrow                 ; r0 = reason code
        LDR     r4, [r12, #DANode_Size]                 ; r4 = new size
        ASSERT  DANode_Handler = DANode_Workspace +4
        ADD     r12, r12, #DANode_Workspace
        MOV     lr, pc
        LDMIA   r12, {r12, pc}                          ; load workspace pointer and jump to handler
        EXIT

; ***********************************************************************************
;
;       MovePageAtR0ToR1WithAccessR6
;
;       Internal routine, called by OS_ChangeDynamicArea
;
; in:   r0 = logical address where page is now
;       r1 = logical address it should be moved to
;       r6 = area flags (which contain access privileges, and cacheable/bufferable bits)
;
; out:  All registers preserved
;

MovePageAtR0ToR1WithAccessR6 ENTRY "r2-r5,r11"
        MOV     r3, r1
        MOV     r11, r6
        BL      MoveCAMatR0toR3         ; use old internal routine for now
        EXIT

; Same as above, but returns with r2 = page number of page that moved

MovePageAtR0ToR1WithAccessR6ReturnPageNumber ENTRY "r3-r5,r11"
        MOV     r3, r1
        MOV     r11, r6
        BL      MoveCAMatR0toR3         ; use old internal routine for now
        EXIT

; ***********************************************************************************
;
;       DynAreaHandler_SysHeap - Dynamic area handler for system heap
;       DynAreaHandler_RMA     - Dynamic area handler for RMA
;
; in:   r0 = reason code (0=>pre-grow, 1=>post-grow, 2=>pre-shrink, 3=>post-shrink)
;       r12 -> base of area
;

DynAreaHandler_SysHeap
DynAreaHandler_RMA ROUT
        CMP     r0, #4
        ADDCC   pc, pc, r0, LSL #2
        B       UnknownHandlerError
        B       PreGrow_Heap
        B       PostGrow_Heap
        B       PreShrink_Heap
        B       PostShrink_Heap

PostGrow_Heap
PostShrink_Heap
        STR     r4, [r12, #:INDEX:hpdend] ; store new size

; and drop thru to...

PreGrow_Heap
        CLRV                            ; don't need to do anything here
        MOV     pc, lr                  ; so just exit

PreShrink_Heap
        Push    "r0, lr"
        MOV     lr, pc                  ; save old IRQ status
        TEQP    pc, #SVC_mode + I_bit   ; disable IRQs round this bit
        LDR     r0, [r12, #:INDEX:hpdbase]      ; get minimum size
        SUB     r0, r4, r0              ; r0 = current-minimum = max shrink
        CMP     r3, r0                  ; if requested shrink > max
        MOVHI   r3, r0                  ; then limit it
        SUB     r0, r5, #1              ; r0 = page mask
        BIC     r3, r3, r0              ; round size change down to page multiple
        SUB     r0, r4, r3              ; area size after shrink
        STR     r0, [r12, #:INDEX:hpdend] ; update size

        TEQP    lr, #0                  ; restore IRQ status
        CLRV
        Pull    "r0, pc"

AreaName_RMA
        =       "Module area", 0
        ALIGN

 ]

 [ NewCDA
UnknownHandlerError
        Push    "lr"
        ADRL    r0, ErrorBlock_UnknownAreaHandler
  [ International
        BL      TranslateError
  ]
        SETV
        Pull    "pc"
 ]

 [ NewStyle_SpriteArea
DynAreaHandler_Sprites
        CMP     r0, #4
        ADDCC   pc, pc, r0, LSL #2
        B       UnknownHandlerError
        B       PreGrow_Sprite
        B       PostGrow_Sprite
        B       PreShrink_Sprite
        B       PostShrink_Sprite

PostGrow_Sprite
PostShrink_Sprite ENTRY "r0"

; in - r3 = size change (+ve), r4 = new size, r5 = page size

        MOV     lr, #VduDriverWorkSpace
        TEQ     r4, #0                  ; if new size = 0
        STREQ   r4, [lr, #SpAreaStart]  ; then set area ptr to zero
        STRNE   r12, [lr, #SpAreaStart] ; else store base address

        MOV     r0, #0
        LDR     lr, [r0, #SpriteSize]   ; load old size
        STR     r4, [r0, #SpriteSize]   ; and store new size
        BEQ     %FT10                   ; if new size is zero, don't try to update header

        STR     r4, [r12, #saEnd]       ; store new size in header
        TEQ     lr, #0                  ; if old size was zero
        STREQ   lr, [r12, #saNumber]    ; then initialise header (no. of sprites = 0)
        MOVEQ   lr, #saExten
        STREQ   lr, [r12, #saFirst]     ; ptr to first sprite -> after header
        STREQ   lr, [r12, #saFree]      ; ptr to first free byte -> after header

10
        CLRV                            ; don't need to do anything here
        EXIT                            ; so just exit

PreGrow_Sprite
        CLRV                            ; don't need to do anything here
        MOV     pc, lr                  ; so just exit

PreShrink_Sprite ENTRY "r0"
        TEQ     r4, #0                  ; if current size is zero
        BEQ     %FT10                   ; then any shrink is OK (shouldn't happen)

        LDR     r0, [r12, #saFree]      ; get used amount
        TEQ     r0, #saExten            ; if only header used,
        MOVEQ   r0, #0                  ; then none really in use

        SUB     r0, r4, r0              ; r0 = current-minimum = max shrink
        CMP     r3, r0                  ; if requested shrink > max
        MOVHI   r3, r0                  ; then limit it
        SUB     r0, r5, #1              ; r0 = page mask
        BIC     r3, r3, r0              ; round size change down to page multiple
10
        CLRV
        EXIT

AreaName_SpriteArea
        =       "System sprites", 0
        ALIGN

 ]

 [ NewStyle_RAMDisc
DynAreaHandler_RAMDisc
        CMP     r0, #4
        ADDCC   pc, pc, r0, LSL #2
        B       UnknownHandlerError
        B       PreGrow_RAMDisc
        B       PostGrow_RAMDisc
        B       PreShrink_RAMDisc
        B       PostShrink_RAMDisc

PostGrow_RAMDisc
PostShrink_RAMDisc ENTRY "r0-r6"

; in - r3 = size change (+ve), r4 = new size, r5 = page size
; but we don't really care about any of these

; The only thing we have to do here is ReInit RAMFS, but NOT if
; a) no modules are initialised yet (eg when we're created), or
; b) RAMFS has been unplugged

        MOV     r0, #0
        LDR     r0, [r0, #Module_List]
        TEQ     r0, #0                  ; any modules yet?
        BEQ     %FT90                   ; no, then don't do anything

        MOV     r0, #ModHandReason_EnumerateROM_Modules
        MOV     r1, #0
        MOV     r2, #-1                 ; enumerate ROM modules looking for RAMFS
10
        SWI     XOS_Module
        BVS     %FT50                   ; no more modules, so it can't be unplugged
        ADR     r5, ramfsname
20
        LDRB    r6, [r3], #1            ; get char from returned module name
        CMP     r6, #" "                ; if a terminator then we have a match
        BLS     %FT30                   ; so check for unplugged
        LowerCase r6, lr                ; else force char to lower case
        LDRB    lr, [r5], #1            ; get char from "ramfs" string
        CMP     lr, r6                  ; and if matches
        BEQ     %BT20                   ; then try next char
        B       %BT10                   ; else try next module

30
        CMP     r4, #-1                 ; is module unplugged?
        BEQ     %FT90                   ; if so, then mustn't reinit it
50
        MOV     r0, #ModHandReason_ReInit ; reinit module
        ADR     r1, ramfsname
        SWI     XOS_Module              ; ignore any errors from this
90
        CLRV
        EXIT

PreGrow_RAMDisc
PreShrink_RAMDisc ENTRY "r0-r5"
        MOV     r0, #0
        LDR     r0, [r0, #Module_List]  ; first check if any modules going
        TEQ     r0, #0
        BEQ     %FT90                   ; if not, don't look at filing system

        MOV     r0, #5
        ADR     r1, ramcolondollardotstar
        SWI     XOS_File
        CMPVC   r0, #0
        BVS     %FT90                   ; if no RAMFS then change OK
        BEQ     %FT90                   ; or if no files, then change OK
        ADR     r0, ErrorBlock_RAMFsUnchangeable
 [ International
        BL      TranslateError
 ]
        STR     r0, [sp]
        SETV
        EXIT

90
        CLRV
        EXIT

        MakeErrorBlock  RAMFsUnchangeable

AreaName_RAMDisc
        =       "RAM disc", 0
ramcolondollardotstar
        =       "ram:$.*", 0
ramfsname
        =       "ramfs", 0
        ALIGN

 ]

 [ NewStyle_FontArea
DynAreaHandler_FontArea
        CMP     r0, #4
        ADDCC   pc, pc, r0, LSL #2
        B       UnknownHandlerError
        B       PreGrow_FontArea
        B       PostGrow_FontArea
        B       PreShrink_FontArea
        B       PostShrink_FontArea

PostGrow_FontArea ENTRY "r0-r2"

; in - r3 = size change (+ve), r4 = new size, r5 = page size

        MOV     r1, #0
        LDR     r1, [r1, #Module_List]  ; any modules active?
        TEQ     r1, #0
        MOVNE   r1, r4                  ; there are, so inform font manager of size change
        SWINE   XFont_ChangeArea
        CLRV
        EXIT

PostShrink_FontArea
PreGrow_FontArea
        CLRV                            ; don't need to do anything here
        MOV     pc, lr                  ; so just exit

PreShrink_FontArea ENTRY "r0-r2"
        MOV     r1, #-1                 ; ask font manager for minimum size of font area
        MOV     r2, #0                  ; default value if no font manager
        SWI     XFont_ChangeArea        ; out: r2 = minimum size

        SUB     r0, r4, r2              ; r0 = current-minimum = max shrink
        CMP     r3, r0                  ; if requested shrink > max
        MOVHI   r3, r0                  ; then limit it
        SUB     r0, r5, #1              ; r0 = page mask
        BIC     r3, r3, r0              ; round size change down to page multiple

        SUB     r1, r4, r3              ; r1 = new size
        SWI     XFont_ChangeArea        ; tell font manager to reduce usage

        CLRV
        EXIT

AreaName_FontArea
        =       "Font cache", 0
        ALIGN

 ]

; **** New screen stuff ****
;
;
; This source collects together all the new routines needed to make
; the screen into a new dynamic area.
;
; It has the following dependencies elsewhere in the kernel before
; it can be expected to work:
;
; * Symbol NewStyle_Screen defined TRUE in GetAll
; * Definition of AP_Screen in ChangeDyn needs doubly_mapped and
;   name_is_token bits set
; * name_is_token handling needs adding (or scrap the bit designation)
; * Call to CreateNewScreenArea from NewReset to create area
; * Tim says doubly-mapped areas are broken - this must be fixed first
; * Old CDA routine may be retired, since screen is its last client
; * Has Tim completed the rest of this work?
;
; Once these routines work, they should be grafted into appropriate
; places in the kernel sources
;
; This source is not intended for stand-alone assembly: it should be
; plumbed into the kernel source build
;
; Version history - remove this once integrated with kernel sources
;
; Vsn  Date      Who  What
; ---  --------  ---  ----------------------------------------------
; 000  23/08/93  amg  Written
; 001  24/08/93  amg  Fixes and changes following review by TMD
; 002  03/09/93  tmd  Updated to work!

; *********************************************************************
; Create a new style dynamic area for the screen
; *********************************************************************

; Entry requirements
; none

        [ NewStyle_Screen
AreaName_Screen
        =       "Screen memory",0               ;needs replacing with message token
        ALIGN

; *********************************************************************
; Handler despatch routine for screen dynamic area
; *********************************************************************

DynAreaHandler_Screen                           ;despatch routine for pre/post grow/shrink handlers
        CMP     r0, #4
        ADDCC   pc, pc, R0, LSL #2
        B       UnknownHandlerError             ;already defined in ChangeDyn
        B       PreGrow_Screen                  ;the rest are defined here
        B       PostGrow_Screen
        B       PreShrink_Screen
        B       PostShrink_Screen

;The sequence of events which these handlers must do is:
;
;Grow Screen
;
;Pre : Remove cursors
;      Work out which physical page numbers are needed and return a list
;CDA : Move existing pages lower in memory within first copy (ie change logical address
;        associated with physical pages)
;      Locate and free the next physical pages in line (if used a page swap must occur)
;      Assign the new pages logical addresses in the gap between the end of the present
;        logical range and the start of the second physical range
;Post: Adjust screen memory contents & screen start addresses to retain screen display
;
;Shrink Screen
;
;Pre : Remove cursors
;      Adjust screen memory contents & screen start addresses to retain screen display
;CDA : Move pages from screen to free pool (creates a gap in first logical range)
;      Close up the gap in logical addressing
;Post: Restore cursors
;

; ***********************************************************************************
; Handlers for the screen dynamic area
; ***********************************************************************************

;Pregrow entry parameters
; R0 = 0 (reason code)
; R1 -> page block (entries set to -1)
; R2 = number of entries in page block == number of pages area is growing by
; R3 = number of bytes area is growing by (r2 * pagesize)
; R4 = current size (bytes)
; R5 = page size
;
; exit with V clear, all preserved

PreGrow_Screen  ENTRY   "r0-r2,r4"
        LDR     r0, [WsPtr, #CursorFlags]       ; test if VDU inited yet
        TEQ     r0, #0                          ; if not, CursorFlags will be zero
        SWINE   XOS_RemoveCursors               ; if VDU inited, then remove cursors

        ADRL    r0, PageShifts-1
        LDRB    r0, [r0, r5, LSR #12]           ; grab log2Pagesize for shifting
        MOV     r4, r4, LSR r0                  ; change present size into number of pages
                                                ; since page numbers are 0 to n-1 thus n
                                                ; is the first page number we want to insist on
10
        STR     r4, [r1], #12                   ; store physical page number and increment to next
        SUBS    r2, r2, #1                      ; one less to do
        ADDNE   r4, r4, #1                      ; next physical page number
        BNE     %BT10                           ; continue until all pages done
        CLRV                                    ; ok, so I'm paranoid...
        EXIT

; **********************************************************************

;PostGrow entry parameters
;R0 = 1 (reason code)
;R1 -> page block (only physical page numbers are meaningful)
;R2 = number of entries in page block (= number of pages area grew by)
;R3 = number of bytes area grew by
;R4 = new size of area (bytes)
;R5 = page size

PostGrow_Screen ENTRY   "r0,r5"
        LDR     r0, [WsPtr, #CursorFlags]       ; test if VDU inited (CursorFlags=0 => not)
        TEQ     r0, #0
        BEQ     %FT90                           ; if not inited, do nothing

        MOV     r5, pc
        TEQP    pc, #SVC_mode+I_bit             ; disable IRQs

        MOV     r0, r3                          ; move number of bytes area grew by into r0
        BL      InsertPages                     ; only call InsertPages if VDU inited

        TEQP    r5, #0                          ; restore IRQ state
        SWI     XOS_RestoreCursors              ; and restore cursors
90
        CLRV
        EXIT

; ***********************************************************************

;PreShrink Entry parameters
;R0 = 2 (reason code)
;R3 = number of bytes area is shrinking by
;R4 = current size of area (bytes)
;R5 = page size
;R12 = vdu workspace

PreShrink_Screen ENTRY   "R0-R2,R4-R5"

        ;need to check whether the proposed shrink still leaves enough for
        ;the current amount needed by the vdu drivers, if it doesn't we
        ;reduce R3 to be the most we can spare (in whole pages)

        SUB     R2, R5, #1                      ;make a page mask

        LDR     R5, [R12, #ScreenSize]          ;get current minimum size

        SUB     R1, R4, R5                      ;R1 = maximum shrink (current - screensize)
        CMP     R3, R1                          ;if requested shrink > max...
        MOVHI   R3, R1                          ;...then limit it, and...
        BICS    R3, R3, R2                      ;...round down to multiple of page size
        BEQ     %FT10                           ;don't shuffle screen data if resultant
                                                ;shrink is 0 bytes/0 pages
        SWI     XOS_RemoveCursors
        MOV     R5, PC
        TEQP    PC, #SVC_mode+I_bit             ;disable interrupts
        RSB     R0, R3, #0                      ;R0= -(number of bytes) for RemovePages
        BL      RemovePages                     ;entry: R0 = -(number of bytes)
        TEQP    PC, R5                          ;restore interrupts
10
        CLRV
        EXIT

; ************************************************************************

;PostShrink Entry parameters
;R0 = 3 (reason code)
;R3 = number of bytes area shrank by
;R4 = new size of area (bytes)
;R5 = page size

PostShrink_Screen ENTRY
        SWI     XOS_RestoreCursors
        CLRV                                    ;ok, so I'm paranoid...
        EXIT

; ************************************************************************

 ]

        END