[project @ 2002-11-20 14:09:42 by simonmar]
[ghc-hetmet.git] / ghc / utils / genapply / GenApply.hs
1 {-# OPTIONS -cpp #-}
2 module Main(main) where
3
4 #include "config.h"
5 #include "MachRegs.h"
6
7 #if __GLASGOW_HASKELL__ >= 504
8 import Text.PrettyPrint
9 import Data.Word
10 import Data.Bits
11 import Data.List        ( intersperse )
12 import Data.Char        ( toUpper )
13 #else
14 import Bits
15 import Word
16 import Pretty
17 import List             ( intersperse )
18 import Char             ( toUpper )
19 #endif
20
21
22 -- -----------------------------------------------------------------------------
23 -- Argument kinds (rougly equivalent to PrimRep)
24
25 data ArgRep 
26   = N           -- non-ptr
27   | P           -- ptr
28   | V           -- void
29   | F           -- float
30   | D           -- double
31   | L           -- long (64-bit)
32
33 -- size of a value in *words*
34 argSize :: ArgRep -> Int
35 argSize N = 1
36 argSize P = 1
37 argSize V = 0
38 argSize F = 1
39 argSize D = (SIZEOF_DOUBLE `quot` SIZEOF_VOID_P :: Int)
40 argSize L = (8 `quot` SIZEOF_VOID_P :: Int)
41
42 showArg :: ArgRep -> Char
43 showArg N = 'n'
44 showArg P = 'p'
45 showArg V = 'v'
46 showArg F = 'f'
47 showArg D = 'd'
48 showArg L = 'l'
49
50 -- is a value a pointer?
51 isPtr :: ArgRep -> Bool
52 isPtr P = True
53 isPtr _ = False
54
55 -- -----------------------------------------------------------------------------
56 -- Registers
57
58 type Reg = String
59
60 availableRegs :: ([Reg],[Reg],[Reg],[Reg])
61 availableRegs = 
62   ( vanillaRegs MAX_REAL_VANILLA_REG,
63     floatRegs   MAX_REAL_FLOAT_REG,
64     doubleRegs  MAX_REAL_DOUBLE_REG,
65     longRegs    MAX_REAL_LONG_REG
66   )
67
68 vanillaRegs, floatRegs, doubleRegs, longRegs :: Int -> [Reg]
69 vanillaRegs n = [ "R" ++ show m ++ ".w" | m <- [2..n] ]  -- never use R1
70 floatRegs   n = [ "F" ++ show m | m <- [1..n] ]
71 doubleRegs  n = [ "D" ++ show m | m <- [1..n] ]
72 longRegs    n = [ "L" ++ show m | m <- [1..n] ]
73
74 -- -----------------------------------------------------------------------------
75 -- Loading/saving register arguments to the stack
76
77 loadRegArgs :: Int -> [ArgRep] -> (Doc,Int)
78 loadRegArgs sp args = (vcat (map (uncurry assign_stk_to_reg) reg_locs), sp')
79  where
80   (reg_locs, sp') = assignRegs sp args
81
82 -- a bit like assignRegs in CgRetConv.lhs
83 assignRegs
84         :: Int                  -- Sp of first arg
85         -> [ArgRep]             -- args
86         -> ([(Reg,Int)], Int)   -- Sp and rest of args
87 assignRegs sp args = assign sp args availableRegs []
88
89 assign sp [] regs doc = (doc, sp)
90 assign sp (V : args) regs doc = assign sp args regs doc
91 assign sp (arg : args) regs doc
92  = case findAvailableReg arg regs of
93     Just (reg, regs') -> assign (sp + argSize arg)  args regs' 
94                             ((reg, sp) : doc)
95     Nothing -> (doc, sp)
96
97 findAvailableReg N (vreg:vregs, fregs, dregs, lregs) =
98   Just (vreg, (vregs,fregs,dregs,lregs))
99 findAvailableReg P (vreg:vregs, fregs, dregs, lregs) =
100   Just (vreg, (vregs,fregs,dregs,lregs))
101 findAvailableReg F (vregs, freg:fregs, dregs, lregs) =
102   Just (freg, (vregs,fregs,dregs,lregs))
103 findAvailableReg D (vregs, fregs, dreg:dregs, lregs) =
104   Just (dreg, (vregs,fregs,dregs,lregs))
105 findAvailableReg L (vregs, fregs, dregs, lreg:lregs) =
106   Just (lreg, (vregs,fregs,dregs,lregs))
107 findAvailableReg _ _ = Nothing
108
109 assign_reg_to_stk reg@('F':_) sp
110    = text "ASSIGN_FLT(Sp+" <> int sp <> comma <> text reg <> text ");"
111 assign_reg_to_stk reg@('D':_) sp
112    = text "ASSIGN_DBL(Sp+" <> int sp <> comma <> text reg <> text ");"
113 assign_reg_to_stk reg@('L':_) sp
114    = text "ASSIGN_Word64(Sp+" <> int sp <> comma <> text reg <> text ");"
115 assign_reg_to_stk reg sp
116    = text "Sp[" <> int sp <> text "] = " <> text reg <> semi
117
118 assign_stk_to_reg reg@('F':_) sp
119    = text reg <> text " = "  <> text "PK_FLT(Sp+" <> int sp <> text ");"
120 assign_stk_to_reg reg@('D':_) sp
121    = text reg <> text " = "  <> text "PK_DBL(Sp+" <> int sp <> text ");"
122 assign_stk_to_reg reg@('L':_) sp
123    = text reg <> text " = "  <> text "PK_Word64(Sp+" <> int sp <> text ");"
124 assign_stk_to_reg reg sp
125    = text reg <> text " = Sp[" <> int sp <> text "];"
126
127
128 -- make a ptr/non-ptr bitmap from a list of argument types
129 mkBitmap :: [ArgRep] -> Word32
130 mkBitmap args = foldr f 0 args
131  where f arg bm | isPtr arg = bm `shiftL` 1
132                 | otherwise = (bm `shiftL` size) .|. ((1 `shiftL` size) - 1)
133                 where size = argSize arg
134
135 -- -----------------------------------------------------------------------------
136 -- Generating the application functions
137
138 mkApplyRetName args
139   = text "stg_ap_" <> text (map showArg args) <> text "_ret"
140
141 mkApplyInfoName args
142   = text "stg_ap_" <> text (map showArg args) <> text "_info"
143
144 genMkPAP macro jump is_pap args all_args_size fun_info_label
145   =  smaller_arity_cases
146   $$ exact_arity_case
147   $$ larger_arity_case
148         
149   where
150     n_args = length args
151
152 -- The SMALLER ARITY cases:
153 --      if (arity == 1) {
154 --          Sp[0] = Sp[1];
155 --          Sp[1] = (W_)&stg_ap_1_info;
156 --          JMP_(GET_ENTRY(R1.cl));
157
158     smaller_arity_cases = vcat [ smaller_arity i | i <- [1..n_args-1] ]
159
160     smaller_arity arity
161         =  text "if (arity == " <> int arity <> text ") {" $$
162            let
163              (reg_doc, sp')
164                 | is_pap    = (empty, 1)
165                 | otherwise = loadRegArgs 1 these_args
166            in
167            nest 4 (vcat [
168              reg_doc,
169              vcat [ shuffle_down j | j <- [sp'..these_args_size] ],
170              text "Sp[" <> int these_args_size <>  text "] = (W_)&" <>
171                 mkApplyInfoName rest_args <> semi,
172              text "Sp += " <> int (sp' -  1) <> semi,
173                 -- for a PAP, we have to arrange that the stack contains a
174                 -- return address in the even that stg_PAP_entry fails its
175                 -- heap check.  See stg_PAP_entry in Apply.hc for details.
176              if is_pap 
177                 then text "Sp--; Sp[0] = (W_)&" <> mkApplyInfoName these_args <> semi
178                 else empty,
179              text "JMP_" <> parens (text jump) <> semi
180             ]) $$
181            text "}"
182         where
183                 (these_args, rest_args) = splitAt arity args
184                 these_args_size = sum (map argSize these_args)
185                 
186                 shuffle_down i = 
187                   text "Sp[" <> int (i-1) <> text "] = Sp["
188                      <> int i <> text "];"
189
190 -- The EXACT ARITY case
191 --
192 --      if (arity == 1) {
193 --          Sp++;
194 --          JMP_(GET_ENTRY(R1.cl));
195
196     exact_arity_case 
197         = text "if (arity == " <> int n_args <> text ") {" $$
198           let
199              (reg_doc, sp')
200                 | is_pap    = (empty, 0)
201                 | otherwise = loadRegArgs 1 args
202           in
203           nest 4 (vcat [
204             reg_doc,
205             text "Sp += " <> int sp' <> semi,
206             if is_pap 
207                 then text "Sp[0] = (W_)&" <> fun_info_label <> semi
208                 else empty,
209             text "JMP_" <> parens (text jump) <> semi
210           ])
211
212 -- The LARGER ARITY cases:
213 --
214 --      } else /* arity > 1 */ {
215 --          BUILD_PAP(1,0,(W_)&stg_ap_v_info);
216 --      }
217
218     larger_arity_case = 
219            text "} else {" $$
220            nest 4 (
221                 text macro <> char '(' <> int n_args <> comma <> 
222                                         int all_args_size <>  
223                                         text ",(W_)&" <> fun_info_label <>
224                                         text ");"
225            ) $$
226            char '}'
227
228 -- -----------------------------------------------------------------------------
229 -- generate an apply function
230
231 -- args is a list of 'p', 'n', 'f', 'd' or 'l'
232
233 genApply args =
234    let
235     fun_ret_label  = mkApplyRetName args
236     fun_info_label = mkApplyInfoName args
237     all_args_size  = sum (map argSize args)
238    in
239     vcat [
240       text "INFO_TABLE_RET(" <> fun_info_label <> text "," <>
241         fun_ret_label <> text "," <>
242         text "MK_SMALL_BITMAP(" <> int all_args_size <> text "/*framsize*/," <>
243         int (fromIntegral (mkBitmap args)) <> text "/*bitmap*/), " <>
244         text "0,0,0,RET_SMALL,,EF_,0,0);",
245       text "",
246       text "F_ " <> fun_ret_label <> text "( void )\n{",
247       nest 4 (vcat [
248        text "StgInfoTable *info;",
249        text "nat arity;",
250
251 --    if fast == 1:
252 --        print "static void *lbls[] ="
253 --        print "  { [FUN]             &&fun_lbl,"
254 --        print "    [FUN_1_0]         &&fun_lbl,"
255 --        print "    [FUN_0_1]        &&fun_lbl,"
256 --        print "    [FUN_2_0]        &&fun_lbl,"
257 --        print "    [FUN_1_1]        &&fun_lbl,"
258 --        print "    [FUN_0_2]        &&fun_lbl,"
259 --        print "    [FUN_STATIC]      &&fun_lbl,"
260 --        print "    [PAP]             &&pap_lbl,"
261 --        print "    [THUNK]           &&thunk_lbl,"
262 --        print "    [THUNK_1_0]              &&thunk_lbl,"
263 --        print "    [THUNK_0_1]              &&thunk_lbl,"
264 --        print "    [THUNK_2_0]              &&thunk_lbl,"
265 --        print "    [THUNK_1_1]              &&thunk_lbl,"
266 --        print "    [THUNK_0_2]              &&thunk_lbl,"
267 --        print "    [THUNK_STATIC]    &&thunk_lbl,"
268 --        print "    [THUNK_SELECTOR]  &&thunk_lbl,"
269 --        print "    [IND]            &&ind_lbl,"
270 --        print "    [IND_OLDGEN]      &&ind_lbl,"
271 --        print "    [IND_STATIC]      &&ind_lbl,"
272 --        print "    [IND_PERM]       &&ind_lbl,"
273 --        print "    [IND_OLDGEN_PERM] &&ind_lbl"
274 --        print "  };"
275     
276        text "FB_",
277        text "",
278        text "IF_DEBUG(apply,fprintf(stderr, \"" <> fun_ret_label <> 
279           text "... \"); printClosure(R1.cl));",
280        text "IF_DEBUG(sanity,checkStackChunk(Sp+" <> int (1 + all_args_size) <>
281           text ", CurrentTSO->stack + CurrentTSO->stack_size));",
282     
283        text "TICK_SLOW_CALL(" <> int (length args) <> text ");",
284
285        let do_assert [] _ = []
286            do_assert (arg:args) offset
287                 | isPtr arg = this : rest
288                 | otherwise = rest
289                 where this = text "ASSERT(LOOKS_LIKE_CLOSURE_PTR(Sp[" 
290                                  <> int offset <> text "]));"
291                       rest = do_assert args (offset + argSize arg)
292        in
293        vcat (do_assert args 1),
294          
295        text  "again:",
296        text  "info = get_itbl(R1.cl);",
297
298 --    if fast == 1:
299 --        print "    goto *lbls[info->type];";
300 --    else:
301         text "switch (info->type) {" $$
302          nest 4 (vcat [
303
304 --    if fast == 1:
305 --        print "    fun_lbl:"
306 --    else:
307         text "case FUN:",
308         text "case FUN_1_0:",
309         text "case FUN_0_1:",
310         text "case FUN_2_0:",
311         text "case FUN_1_1:",
312         text "case FUN_0_2:",
313         text "case FUN_STATIC:",
314         nest 4 (vcat [
315           text "arity = itbl_to_fun_itbl(info)->arity;",
316           text "ASSERT(arity > 0);",
317           genMkPAP "BUILD_PAP" "GET_ENTRY(R1.cl)" False{-not PAP-}
318                 args all_args_size fun_info_label
319          ]),
320
321 --    if fast == 1:
322 --        print "    pap_lbl:"
323 --    else:
324
325         text "case PAP:",
326         nest 4 (vcat [
327           text "arity = ((StgPAP *)R1.p)->arity;",
328           text "ASSERT(arity > 0);",
329           genMkPAP "NEW_PAP" "stg_PAP_entry" True{-is PAP-}
330                 args all_args_size fun_info_label
331          ]),
332
333         text "",
334
335 --    if fast == 1:
336 --        print "    thunk_lbl:"
337 --    else:
338         text "case THUNK:",
339         text "case THUNK_1_0:",
340         text "case THUNK_0_1:",
341         text "case THUNK_2_0:",
342         text "case THUNK_1_1:",
343         text "case THUNK_0_2:",
344         text "case THUNK_STATIC:",
345         text "case THUNK_SELECTOR:",
346         nest 4 (vcat [
347           text "Sp[0] = (W_)&" <> fun_info_label <> text ";",
348           text "JMP_(GET_ENTRY(R1.cl));",
349           text ""
350          ]),
351
352 --    if fast == 1:
353 --        print "    ind_lbl:"
354 --    else:
355         text "case IND:",
356         text "case IND_OLDGEN:",
357         text "case IND_STATIC:",
358         text "case IND_PERM:",
359         text "case IND_OLDGEN_PERM:",
360         nest 4 (vcat [
361           text "R1.cl = ((StgInd *)R1.p)->indirectee;",
362           text "goto again;"
363          ]),
364         text "",
365
366 --    if fast == 0:
367
368        text "default:",
369        nest 4 (
370          text "barf(\"" <> fun_ret_label <> text "\");"
371        ),
372        text "}"
373         
374         ])
375       ]),
376       text "FE_",
377       text "}"
378     ]
379
380 -- -----------------------------------------------------------------------------
381 -- Making a stack apply
382
383 -- These little functions are like slow entry points.  They provide
384 -- the layer between the PAP entry code and the function's fast entry
385 -- point: namely they load arguments off the stack into registers (if
386 -- available) and jump to the function's entry code.
387 --
388 -- On entry: R1 points to the function closure
389 --           arguments are on the stack starting at Sp
390 --
391 -- Invariant: the list of arguments never contains void.  Since we're only
392 -- interested in loading arguments off the stack here, we can ignore
393 -- void arguments.
394
395 mkStackApplyEntryLabel:: [ArgRep] -> Doc
396 mkStackApplyEntryLabel args = text "stg_ap_stk_" <> text (map showArg args)
397
398 genStackApply :: [ArgRep] -> Doc
399 genStackApply args = 
400   let fn_entry_label = mkStackApplyEntryLabel args in
401   vcat [
402     text "IFN_" <> parens fn_entry_label,
403     text "{",
404     nest 4 (text "FB_" $$ body $$ text "FE_"),
405     text "}"
406    ]
407  where
408    (assign_regs, sp') = loadRegArgs 0 args
409    body = vcat [assign_regs,
410                 text "Sp += " <> int sp' <> semi,
411                 text "JMP_(GET_ENTRY(R1.cl))"
412                 ]
413
414 -- -----------------------------------------------------------------------------
415 -- Stack save entry points.
416 --
417 -- These code fragments are used to save registers on the stack at a heap
418 -- check failure in the entry code for a function.  We also have to save R1
419 -- and the return address (stg_gen_ap_info) on the stack.  See stg_fun_gc_gen
420 -- in HeapStackCheck.hc for more details.
421
422 mkStackSaveEntryLabel :: [ArgRep] -> Doc
423 mkStackSaveEntryLabel args = text "stg_stk_save_" <> text (map showArg args)
424
425 genStackSave :: [ArgRep] -> Doc
426 genStackSave args =
427   let fn_entry_label= mkStackSaveEntryLabel args in
428   vcat [
429     text "IFN_" <> parens fn_entry_label,
430     text "{",
431     nest 4 (text "FB_" $$ body $$ text "FE_"),
432     text "}"
433    ]
434  where
435    body = vcat [text "Sp -= " <> int sp_offset <> semi,
436                 vcat (map (uncurry assign_reg_to_stk) reg_locs),
437                 text "Sp[2] = R1.w;",
438                 text "Sp[1] =" <+> int (sp_offset - std_frame_size) <> semi,
439                 text "Sp[0] = (W_)&stg_gc_fun_info;",
440                 text "JMP_(stg_gc_noregs);"
441                 ]
442
443    std_frame_size = 3 -- the std bits of the frame. See StgRetFun in Closures.h,
444                       -- and the comment on stg_fun_gc_gen in HeapStackCheck.hc.
445    (reg_locs, sp_offset) = assignRegs std_frame_size args
446
447 -- -----------------------------------------------------------------------------
448 -- The prologue...
449
450 main = putStr (render the_code)
451   where the_code = vcat [
452                 text "// DO NOT EDIT!",
453                 text "// Automatically generated by GenApply.hs",
454                 text "",
455                 text "#include \"Stg.h\"",
456                 text "#include \"Rts.h\"",
457                 text "#include \"RtsFlags.h\"",
458                 text "#include \"Storage.h\"",
459                 text "#include \"RtsUtils.h\"",
460                 text "#include \"Printer.h\"",
461                 text "#include \"Sanity.h\"",
462                 text "#include \"Apply.h\"",
463                 text "",
464                 text "#include <stdio.h>",
465
466                 vcat (intersperse (text "") $ map genApply applyTypes),
467                 vcat (intersperse (text "") $ map genStackFns stackApplyTypes),
468
469                 genStackApplyArray stackApplyTypes,
470                 genStackSaveArray stackApplyTypes,
471                 genBitmapArray stackApplyTypes,
472
473                 text ""  -- add a newline at the end of the file
474             ]
475
476 -- These have been shown to cover about 99% of cases in practice...
477 applyTypes = [
478         [V],
479         [F],
480         [D],
481         [L],
482         [N],
483         [P],
484         [P,V],
485         [P,P],
486         [P,P,V],
487         [P,P,P],
488         [P,P,P,P],
489         [P,P,P,P,P],
490         [P,P,P,P,P,P],
491         [P,P,P,P,P,P,P]
492    ]
493
494 -- No need for V args in the stack apply cases.
495 -- ToDo: the stack apply and stack save code doesn't make a distinction
496 -- between N and P (they both live in the same register), only the bitmap
497 -- changes, so we could share the apply/save code between lots of cases.
498 stackApplyTypes = [
499         [N],
500         [P],
501         [F],
502         [D],
503         [L],
504         [N,N],
505         [N,P],
506         [P,N],
507         [P,P],
508         [N,N,N],
509         [N,N,P],
510         [N,P,N],
511         [N,P,P],
512         [P,N,N],
513         [P,N,P],
514         [P,P,N],
515         [P,P,P],
516         [P,P,P,P],
517         [P,P,P,P,P],
518         [P,P,P,P,P,P],
519         [P,P,P,P,P,P,P],
520         [P,P,P,P,P,P,P,P]
521    ]
522
523 genStackFns args = genStackApply args $$ genStackSave args
524
525
526 genStackApplyArray types =
527   text "StgFun *stg_ap_stack_entries[] = {" $$  
528   vcat (map arr_ent types) $$
529   text "};"
530  where
531   arr_ent ty = brackets (arg_const ty) <+> mkStackApplyEntryLabel ty <> comma
532
533 genStackSaveArray types =
534   text "StgFun *stg_stack_save_entries[] = {" $$  
535   vcat (map arr_ent types) $$
536   text "};"
537  where
538   arr_ent ty = brackets (arg_const ty) <+> mkStackSaveEntryLabel ty <> comma
539
540 genBitmapArray :: [[ArgRep]] -> Doc
541 genBitmapArray types =
542   vcat [
543     text "StgWord stg_arg_bitmaps[] = {",
544     vcat (map gen_bitmap types),
545     text "};"
546   ]
547   where
548    gen_bitmap ty = brackets (arg_const ty) <+> 
549                    text "MK_SMALL_BITMAP" <> parens (
550                         int (sum (map argSize ty)) <> comma <>
551                         text (show (mkBitmap ty))) <>
552                    comma
553
554 arg_const ty = text "ARG_" <> text (map toUpper (map showArg ty))
555