[Git][ghc/ghc][wip/ghci-primcall] fix some docs and not references
Luite Stegeman (@luite)
gitlab at gitlab.haskell.org
Sun Jan 8 15:07:31 UTC 2023
Luite Stegeman pushed to branch wip/ghci-primcall at Glasgow Haskell Compiler / GHC
Commits:
858961bc by Luite Stegeman at 2023-01-09T00:06:47+09:00
fix some docs and not references
- - - - -
4 changed files:
- compiler/GHC/ByteCode/Instr.hs
- compiler/GHC/Cmm/Reg.hs
- compiler/GHC/StgToByteCode.hs
- compiler/GHC/StgToCmm/Foreign.hs
Changes:
=====================================
compiler/GHC/ByteCode/Instr.hs
=====================================
@@ -271,8 +271,8 @@ instance Outputable BCInstr where
ppr (PUSH_ALTS bco) = hang (text "PUSH_ALTS") 2 (ppr bco)
ppr (PUSH_ALTS_UNLIFTED bco pk) = hang (text "PUSH_ALTS_UNLIFTED" <+> ppr pk) 2 (ppr bco)
- ppr (PUSH_ALTS_TUPLE bco tuple_info tuple_bco) =
- hang (text "PUSH_ALTS_TUPLE" <+> ppr tuple_info)
+ ppr (PUSH_ALTS_TUPLE bco call_info tuple_bco) =
+ hang (text "PUSH_ALTS_TUPLE" <+> ppr call_info)
2
(ppr tuple_bco $+$ ppr bco)
@@ -385,9 +385,9 @@ bciStackUse (PUSH_ALTS bco) = 2 {- profiling only, restore CCCS -} +
bciStackUse (PUSH_ALTS_UNLIFTED bco _) = 2 {- profiling only, restore CCCS -} +
4 + protoBCOStackUse bco
bciStackUse (PUSH_ALTS_TUPLE bco info _) =
- -- (tuple_bco, tuple_info word, cont_bco, stg_ctoi_t)
+ -- (tuple_bco, call_info word, cont_bco, stg_ctoi_t)
-- tuple
- -- (tuple_info, tuple_bco, stg_ret_t)
+ -- (call_info, tuple_bco, stg_ret_t)
1 {- profiling only -} +
7 + fromIntegral (nativeCallSize info) + protoBCOStackUse bco
bciStackUse (PUSH_PAD8) = 1 -- overapproximation
=====================================
compiler/GHC/Cmm/Reg.hs
=====================================
@@ -223,7 +223,7 @@ instance Eq GlobalReg where
_r1 == _r2 = False
-- NOTE: this Ord instance affects the tuple layout in GHCi, see
--- Note [GHCi tuple layout]
+-- Note [GHCi and native call registers]
instance Ord GlobalReg where
compare (VanillaReg i _) (VanillaReg j _) = compare i j
-- Ignore type when seeking clashes
=====================================
compiler/GHC/StgToByteCode.hs
=====================================
@@ -986,8 +986,8 @@ doCase d s p scrut bndr alts
-- unboxed tuples get two more words, the second is a pointer (tuple_bco)
(extra_pointers, extra_slots)
- | ubx_tuple_frame && profiling = ([1], 3) -- tuple_info, tuple_BCO, CCCS
- | ubx_tuple_frame = ([1], 2) -- tuple_info, tuple_BCO
+ | ubx_tuple_frame && profiling = ([1], 3) -- call_info, tuple_BCO, CCCS
+ | ubx_tuple_frame = ([1], 2) -- call_info, tuple_BCO
| otherwise = ([], 0)
bitmap_size = trunc16W $ fromIntegral extra_slots +
@@ -1134,7 +1134,7 @@ usePlainReturn t
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
We have the bytecode instructions RETURN_TUPLE and PUSH_ALTS_TUPLE to
return and receive arbitrary unboxed tuples, respectively. These
- instructions use the helper data tuple_BCO and tuple_info.
+ instructions use the helper data tuple_BCO and call_info.
The helper data is used to convert tuples between GHCs native calling
convention (object code), which uses stack and registers, and the bytecode
@@ -1146,7 +1146,7 @@ usePlainReturn t
=================
Bytecode that returns a tuple first pushes all the tuple fields followed
- by the appropriate tuple_info and tuple_BCO onto the stack. It then
+ by the appropriate call_info and tuple_BCO onto the stack. It then
executes the RETURN_TUPLE instruction, which causes the interpreter
to push stg_ret_t_info to the top of the stack. The stack (growing down)
then looks as follows:
@@ -1157,14 +1157,14 @@ usePlainReturn t
tuple_field_2
...
tuple_field_n
- tuple_info
+ call_info
tuple_BCO
stg_ret_t_info <- Sp
If next_frame is bytecode, the interpreter will start executing it. If
it's object code, the interpreter jumps back to the scheduler, which in
turn jumps to stg_ret_t. stg_ret_t converts the tuple to the native
- calling convention using the description in tuple_info, and then jumps
+ calling convention using the description in call_info, and then jumps
to next_frame.
@@ -1176,13 +1176,13 @@ usePlainReturn t
tuple. The PUSH_ALTS_TUPLE instuction contains three pieces of data:
* cont_BCO: the continuation that receives the tuple
- * tuple_info: see below
+ * call_info: see below
* tuple_BCO: see below
The interpreter pushes these onto the stack when the PUSH_ALTS_TUPLE
instruction is executed, followed by stg_ctoi_tN_info, with N depending
on the number of stack words used by the tuple in the GHC native calling
- convention. N is derived from tuple_info.
+ convention. N is derived from call_info.
For example if we expect a tuple with three words on the stack, the stack
looks as follows after PUSH_ALTS_TUPLE:
@@ -1193,7 +1193,7 @@ usePlainReturn t
cont_free_var_2
...
cont_free_var_n
- tuple_info
+ call_info
tuple_BCO
cont_BCO
stg_ctoi_t3_info <- Sp
@@ -1213,16 +1213,16 @@ usePlainReturn t
that is already on the stack.
- The tuple_info word
+ The call_info word
===================
- The tuple_info word describes the stack and STG register (e.g. R1..R6,
- D1..D6) usage for the tuple. tuple_info contains enough information to
+ The call_info word describes the stack and STG register (e.g. R1..R6,
+ D1..D6) usage for the tuple. call_info contains enough information to
convert the tuple between the stack-only bytecode and stack+registers
GHC native calling conventions.
- See Note [GHCi tuple layout] for more details of how the data is packed
- in a single word.
+ See Note [GHCi and native call registers] for more details of how the
+ data is packed in a single word.
-}
@@ -1240,7 +1240,7 @@ tupleBCO platform info pointers =
-}
invented_name = mkSystemVarName (mkPseudoUniqueE 0) (fsLit "tuple")
- -- the first word in the frame is the tuple_info word,
+ -- the first word in the frame is the call_info word,
-- which is not a pointer
bitmap_size = trunc16W $ 1 + nativeCallSize info
bitmap = intsToReverseBitmap platform (fromIntegral bitmap_size) $
@@ -1264,7 +1264,7 @@ primCallBCO platform args_info pointers =
invented_name = mkSystemVarName (mkPseudoUniqueE 0) (fsLit "primcall")
-- the first three words in the frame are the BCO describing the
- -- pointers in the frame, the tuple_info word and the pointer
+ -- pointers in the frame, the call_info word and the pointer
-- to the Cmm function being called. None of these is a pointer that
-- should be followed by the garbage collector
bitmap_size = trunc16W $ 2 + nativeCallSize args_info
@@ -1321,7 +1321,7 @@ generatePrimCall d s p target _mb_unit _result_ty args
size of arguments plus three words for:
- function pointer to the target
- - tuple_info word
+ - call_info word
- BCO to describe the stack frame
-}
szb = wordsToBytes platform (nativeCallSize args_info + 3)
=====================================
compiler/GHC/StgToCmm/Foreign.hs
=====================================
@@ -362,7 +362,7 @@ emitRestoreRegs = do
-- if((mask & 2) != 0) { Sp_adj(-1); Sp(0) = R2; }
-- if((mask & 1) != 0) { Sp_adj(-1); Sp(0) = R1; }
--
--- See Note [GHCi tuple layout]
+-- See Note [GHCi and native call registers]
emitPushArgRegs :: CmmExpr -> FCode ()
emitPushArgRegs regs_live = do
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/858961bc2641096b33621d16a5a00cb6a334fb2d
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/858961bc2641096b33621d16a5a00cb6a334fb2d
You're receiving this email because of your account on gitlab.haskell.org.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230108/5b300cfc/attachment-0001.html>
More information about the ghc-commits
mailing list