[project @ 1996-03-19 08:58:34 by partain]
[ghc-hetmet.git] / ghc / compiler / codeGen / CgStackery.lhs
1 %
2 % (c) The GRASP/AQUA Project, Glasgow University, 1992-1995
3 %
4 \section[CgStackery]{Stack management functions}
5
6 Stack-twiddling operations, which are pretty low-down and grimy.
7 (This is the module that knows all about stack layouts, etc.)
8
9 \begin{code}
10 #include "HsVersions.h"
11
12 module CgStackery (
13         allocAStack, allocBStack, allocUpdateFrame,
14         adjustRealSps, getFinalStackHW,
15         mkVirtStkOffsets, mkStkAmodes
16
17         -- and to make the interface self-sufficient...
18     ) where
19
20 import StgSyn
21 import CgMonad
22 import AbsCSyn
23
24 import CgUsages         ( getSpBRelOffset )
25 import Maybes           ( Maybe(..) )
26 import PrimRep          ( getPrimRepSize, retPrimRepSize, separateByPtrFollowness )
27 import Util
28 \end{code}
29
30 %************************************************************************
31 %*                                                                      *
32 \subsection[CgStackery-layout]{Laying out a stack frame}
33 %*                                                                      *
34 %************************************************************************
35
36 @mkVirtStkOffsets@ is given a list of arguments.  The first argument
37 gets the {\em largest} virtual stack offset (remember, virtual offsets
38 increase towards the top of stack).
39
40 \begin{code}
41 mkVirtStkOffsets :: VirtualSpAOffset    -- Offset of the last allocated thing
42           -> VirtualSpBOffset           -- ditto
43           -> (a -> PrimRep)     -- to be able to grab kinds
44           -> [a]                        -- things to make offsets for
45           -> (VirtualSpAOffset,         -- OUTPUTS: Topmost allocated word
46               VirtualSpBOffset,         -- ditto
47               [(a, VirtualSpAOffset)],  --  boxed things with offsets
48               [(a, VirtualSpBOffset)])  --  unboxed things with offsets
49
50 mkVirtStkOffsets init_SpA_offset init_SpB_offset kind_fun things
51   = let (boxeds, unboxeds)
52             = separateByPtrFollowness kind_fun things
53         (last_SpA_offset, boxd_w_offsets)
54             = mapAccumR computeOffset init_SpA_offset boxeds
55         (last_SpB_offset, ubxd_w_offsets)
56             = mapAccumR computeOffset init_SpB_offset unboxeds
57     in
58         (last_SpA_offset, last_SpB_offset, boxd_w_offsets, ubxd_w_offsets)
59   where
60     computeOffset offset thing
61       = (offset + (getPrimRepSize . kind_fun) thing, (thing, offset+(1::Int)))
62 \end{code}
63
64 @mkStackAmodes@ is a higher-level version of @mkStackOffsets@.
65 It starts from the tail-call locations.
66 It returns a single list of addressing modes for the stack locations,
67 and therefore is in the monad.
68
69 It also adjusts the high water mark if necessary.
70
71 \begin{code}
72 mkStkAmodes :: VirtualSpAOffset             -- Tail call positions
73             -> VirtualSpBOffset
74             -> [CAddrMode]                  -- things to make offsets for
75             -> FCode (VirtualSpAOffset,     -- OUTPUTS: Topmost allocated word
76                       VirtualSpBOffset,     -- ditto
77                       AbstractC)            -- Assignments to appropriate stk slots
78
79 mkStkAmodes tail_spa tail_spb things
80             info_down (MkCgState absC binds usage)
81   = (result, MkCgState absC binds new_usage)
82   where
83     result = (last_SpA_offset, last_SpB_offset, mkAbstractCs abs_cs)
84
85     (last_SpA_offset, last_SpB_offset, ptrs_w_offsets, non_ptrs_w_offsets)
86         = mkVirtStkOffsets tail_spa tail_spb getAmodeRep things
87
88     abs_cs
89         = [ CAssign (CVal (SpARel realSpA offset) PtrRep) thing
90           | (thing, offset) <- ptrs_w_offsets
91           ]
92           ++
93           [ CAssign (CVal (SpBRel realSpB offset) (getAmodeRep thing)) thing
94           | (thing, offset) <- non_ptrs_w_offsets
95           ]
96
97     ((vspA,fspA,realSpA,hwSpA), (vspB,fspB,realSpB,hwSpB), h_usage) = usage
98
99     new_usage = ((vspA,fspA,realSpA,max last_SpA_offset hwSpA),
100                  (vspB,fspB,realSpB,max last_SpB_offset hwSpB),
101                  h_usage)
102     -- No need to fiddle with virtual SpA etc because this call is
103     -- only done just before the end of a block
104
105
106 \end{code}
107
108 %************************************************************************
109 %*                                                                      *
110 \subsection[CgStackery-monadery]{Inside-monad functions for stack manipulation}
111 %*                                                                      *
112 %************************************************************************
113
114 Allocate a virtual offset for something.
115 \begin{code}
116 allocAStack :: FCode VirtualSpAOffset
117
118 allocAStack info_down (MkCgState absC binds
119                     ((virt_a, free_a, real_a, hw_a), b_usage, h_usage))
120   = (chosen_slot, MkCgState absC binds (new_a_usage, b_usage, h_usage))
121   where
122     push_virt_a = virt_a + 1
123
124     (chosen_slot, new_a_usage)
125         = if null free_a then
126                 -- No free slots, so push a new one
127                 -- We need to adjust the high-water mark
128                 (push_virt_a, (push_virt_a, [], real_a, hw_a `max` push_virt_a))
129           else
130                 -- Free slots available, so use one
131                 (free_slot, (virt_a, new_free_a, real_a, hw_a))
132
133     (free_slot, _) = head ([f | f@(slot, st) <- free_a, not (isStubbed st)] ++ free_a)
134                     -- Try to find an un-stubbed location;
135                     -- if none, return the first in the free list
136                     -- We'll only try this if free_a is known to be non-empty
137
138     -- Free list with the free_slot deleted
139     new_free_a = [ f | f@(s,_) <- free_a, s /= free_slot ]
140
141 allocBStack :: Int -> FCode VirtualSpBOffset
142 allocBStack size info_down (MkCgState absC binds
143                                  (a_usage, (virt_b, free_b, real_b, hw_b), h_usage))
144   = (chosen_slot, MkCgState absC binds (a_usage, new_b_usage, h_usage))
145   where
146     push_virt_b = virt_b + size
147
148     (chosen_slot, new_b_usage)
149         = case find_block free_b of
150                 Nothing -> (virt_b+1, (push_virt_b, free_b, real_b,
151                                        hw_b `max` push_virt_b))
152                                        -- Adjust high water mark
153
154                 Just slot -> (slot, (virt_b, delete_block free_b slot, real_b, hw_b))
155
156     -- find_block looks for a contiguous chunk of free slots
157     find_block :: [VirtualSpBOffset] -> Maybe VirtualSpBOffset
158     find_block [] = Nothing
159     find_block (slot:slots)
160       | take size (slot:slots) == [slot..slot+size-1]
161       = Just slot
162       | otherwise
163       = find_block slots
164
165     delete_block free_b slot = [s | s <- free_b, (s<slot) || (s>=slot+size)]
166                               -- Retain slots which are not in the range
167                               -- slot..slot+size-1
168 \end{code}
169
170 @allocUpdateFrame@ allocates enough space for an update frame
171 on the B stack, records the fact in the end-of-block info (in the ``args''
172 fields), and passes on the old ``args'' fields to the enclosed code.
173
174 This is all a bit disgusting.
175
176 \begin{code}
177 allocUpdateFrame :: Int                 -- Size of frame
178                  -> CAddrMode           -- Return address which is to be the
179                                         -- top word of frame
180                  -> ((VirtualSpAOffset, VirtualSpBOffset, VirtualSpBOffset) -> Code)
181                                                 -- Scope of update
182                  -> Code
183
184 allocUpdateFrame size update_amode code
185         (MkCgInfoDown c_info statics (EndOfBlockInfo args_spa args_spb sequel))
186         (MkCgState absc binds (a_usage, (vB,rr,qq,hwB),h_usage))
187   = case sequel of
188
189         InRetReg -> code (args_spa, args_spb, vB)
190                          (MkCgInfoDown c_info statics new_eob_info)
191                          (MkCgState absc binds new_usage)
192
193         other    -> panic "allocUpdateFrame"
194
195   where
196     new_vB = vB + size
197     new_eob_info = EndOfBlockInfo args_spa new_vB (UpdateCode update_amode)
198     new_usage = (a_usage, (new_vB,rr,qq,hwB `max` new_vB), h_usage)
199 \end{code}
200
201
202 A knot-tying beast.
203
204 \begin{code}
205 getFinalStackHW :: (VirtualSpAOffset -> VirtualSpBOffset -> Code) -> Code
206 getFinalStackHW fcode info_down (MkCgState absC binds usages) = state1
207   where
208     state1 = fcode hwSpA hwSpB info_down (MkCgState absC binds usages)
209     (MkCgState _ _ ((_,_,_, hwSpA), (_,_,_, hwSpB), _)) = state1
210 \end{code}
211
212
213 %************************************************************************
214 %*                                                                      *
215 \subsection[CgStackery-adjust]{Adjusting the stack pointers}
216 %*                                                                      *
217 %************************************************************************
218
219 @adjustRealSpX@ generates code to alter the actual stack pointer, and
220 adjusts the environment accordingly.  We are careful to push the
221 conditional inside the abstract C code to avoid black holes.
222 ToDo: combine together?
223
224 These functions {\em do not} deal with high-water-mark adjustment.
225 That's done by functions which allocate stack space.
226
227 \begin{code}
228 adjustRealSpA :: VirtualSpAOffset       -- New offset for Arg stack ptr
229               -> Code
230 adjustRealSpA newRealSpA info_down (MkCgState absC binds
231                                         ((vspA,fA,realSpA,hwspA),
232                                         b_usage, h_usage))
233   = MkCgState (mkAbsCStmts absC move_instrA) binds new_usage
234     where
235     move_instrA = if (newRealSpA == realSpA) then AbsCNop
236                  else (CAssign
237                             (CReg SpA)
238                             (CAddr (SpARel realSpA newRealSpA)))
239     new_usage = ((vspA, fA, newRealSpA, hwspA),
240                  b_usage, h_usage)
241
242 adjustRealSpB :: VirtualSpBOffset       -- New offset for Basic/Control stack ptr
243               -> Code
244 adjustRealSpB newRealSpB info_down (MkCgState absC binds
245                                         (a_usage,
246                                         (vspB,fB,realSpB,hwspB),
247                                         h_usage))
248   = MkCgState (mkAbsCStmts absC move_instrB) binds new_usage
249     where
250     move_instrB = if (newRealSpB == realSpB) then AbsCNop
251                  else (CAssign {-PtrRep-}
252                             (CReg SpB)
253                             (CAddr (SpBRel realSpB newRealSpB)))
254     new_usage = (a_usage,
255                  (vspB, fB, newRealSpB, hwspB),
256                  h_usage)
257
258 adjustRealSps :: VirtualSpAOffset       -- New offset for Arg stack ptr
259               -> VirtualSpBOffset       -- Ditto B stack
260               -> Code
261 adjustRealSps newRealSpA newRealSpB
262   = adjustRealSpA newRealSpA `thenC` adjustRealSpB newRealSpB
263 \end{code}