[GHC] #6084: Add stg_ap_pnnv and related call patterns
GHC
ghc-devs at haskell.org
Sat Sep 16 04:28:42 UTC 2017
#6084: Add stg_ap_pnnv and related call patterns
-------------------------------------+-------------------------------------
Reporter: SimonMeier | Owner: simonmar
Type: feature request | Status: closed
Priority: high | Milestone: 7.8.1
Component: Runtime System | Version: 7.7
Resolution: fixed | Keywords:
Operating System: Unknown/Multiple | Architecture:
| Unknown/Multiple
Type of failure: None/Unknown | Test Case:
Blocked By: | Blocking: 8313
Related Tickets: | Differential Rev(s):
Wiki Page: |
-------------------------------------+-------------------------------------
Comment (by angerman):
cmm, as per `-ddump-cmm`.
I believe the relevant part is
{{{
==================== Output Cmm ====================
[section ""relreadonly" . S4QA_srt" {
S4QA_srt:
const Main.q1_closure;
},
section ""data" . Main.p_closure" {
Main.p_closure:
const Main.p_info;
const 0;
},
Main.p_slow() // [R1]
{ info_tbl: []
stack_info: arg_space: 0 updfr_space: Nothing
}
{offset
c4Qt: // global
D2 = F64[Sp + 16];
F1 = F32[Sp + 8];
R2 = I64[Sp];
R1 = R1;
Sp = Sp + 24;
call Main.p_info(D2, F1, R2, R1) args: 8, res: 0, upd: 8;
}
},
Main.p_entry() // []
{ info_tbl: [(c4Qx,
label: Main.p_info
rep:HeapRep static {
Fun {arity: 3 fun_type: ArgGen [True, True,
True]} })]
stack_info: arg_space: 0 updfr_space: Nothing
}
{offset
c4Qx: // global
R1 = Main.q1_closure;
call (I64[R1])(R1) args: 8, res: 0, upd: 8;
}
}]
}}}
However, my Cmm knowledge is rather limited.
The llvm backend then does:
{{{
pprLlvmCmmDecl (CmmProc mb_info entry_lbl live (ListGraph blks))
= do let lbl = case mb_info of
Nothing -> entry_lbl
Just (Statics info_lbl _) -> info_lbl
link = if externallyVisibleCLabel lbl
then ExternallyVisible
else Internal
lmblocks = map (\(BasicBlock id stmts) ->
LlvmBlock (getUnique id) stmts) blks
funDec <- llvmFunSig live lbl link
dflags <- getDynFlags
let buildArg = fsLit . showSDoc dflags . ppPlainName
funArgs = map buildArg (llvmFunArgs dflags live)
funSect = llvmFunSection dflags (decName funDec)
-- generate the info table
prefix <- case mb_info of
Nothing -> return Nothing
Just (Statics _ statics) -> do
infoStatics <- mapM genData statics
let infoTy = LMStruct $ map getStatType infoStatics
return $ Just $ LMStaticStruc infoStatics infoTy
let fun = LlvmFunction funDec funArgs llvmStdFunAttrs funSect
prefix lmblocks
name = decName $ funcDecl fun
defName = name `appendFS` fsLit "$def"
funcDecl' = (funcDecl fun) { decName = defName }
fun' = fun { funcDecl = funcDecl' }
funTy = LMFunction funcDecl'
funVar = LMGlobalVar name
(LMPointer funTy)
link
Nothing
Nothing
Alias
defVar = LMGlobalVar defName
(LMPointer funTy)
(funcLinkage funcDecl')
(funcSect fun)
(funcAlign funcDecl')
Alias
alias = LMGlobal funVar
(Just $ LMBitc (LMStaticPointer defVar)
(LMPointer $ LMInt 8))
return (ppLlvmGlobal alias $+$ ppLlvmFunction fun', [])
-- ...
llvmFunSig :: LiveGlobalRegs -> CLabel -> LlvmLinkageType -> LlvmM
LlvmFunctionDecl
llvmFunSig live lbl link = do
lbl' <- strCLabel_llvm lbl
llvmFunSig' live lbl' link
llvmFunSig' :: LiveGlobalRegs -> LMString -> LlvmLinkageType -> LlvmM
LlvmFunctionDecl
llvmFunSig' live lbl link
= do let toParams x | isPointer x = (x, [NoAlias, NoCapture])
| otherwise = (x, [])
dflags <- getDynFlags
return $ LlvmFunctionDecl lbl link (llvmGhcCC dflags) LMVoid
FixedArgs
(map (toParams . getVarType) (llvmFunArgs
dflags live))
(llvmFunAlign dflags)
-- ...
-- | A Function's arguments
llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar]
llvmFunArgs dflags live =
map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform))
where platform = targetPlatform dflags
isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live
isPassed r = not (isSSE r) || isLive r
isSSE (FloatReg _) = True
isSSE (DoubleReg _) = True
isSSE (XmmReg _) = True
isSSE (YmmReg _) = True
isSSE (ZmmReg _) = True
isSSE _ = False
-- ...
-- | A list of STG Registers that should always be considered alive
alwaysLive :: [GlobalReg]
alwaysLive = [BaseReg, Sp, Hp, SpLim, HpLim, node]
}}}
As the set of live registers for `Main.p_info` (`Main.p_entry()`) is
empty, we end up generating the default signature for
{{{
["BaseReg","Sp","Hp","R1","R2","R3","R4","R5","R6","SpLim"]
}}}
only, when we supposedly would want to have included `F1` and `D2` as
well. On the other hand, I don't see where we'd use those in the body of
`p_entry`. And thus why we'd want to pass them in the first place?
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/6084#comment:37>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list