Simon Marlow wrote:
In fact, I'm surprised at how much there is here. The LLVM backend has
more in common with the native code generators than the C backend, but I
was expecting something closer to a straightforward pretty-printer. I
wonder if having a complete datatype for LLVM is really buying us
anything since we don't actually do anything to it other than print it
out. As a quick example of what I mean, what would be lost if we replace

data LlvmCastOp
= LM_Trunc
| LM_Zext
... lots of constructors ...
deriving (Eq)

instance Show LlvmCastOp where
show LM_Trunc = "trunc"
show LM_Zext = "zext"
...

with

type LlvmCastOp = FastString
lM_Trunc = fsLit "trunc"
...


At the moment, nothing.


Do we envisage doing anything complex to the Llvm code inside GHC in the
future? I can't think of a reason to.

One thing I would like to investigate at some point is to have the LLVM binding use the C++ API of LLVM instead of printing out LLVM Assembly. This should potentially speed up the compilation process since it would replace the current 4 passes (generate LLVM Assembly, convert to bitcode [llvm-as], optimise [opt], compile to native code [llc]). With just one. I believe the current design would be easier to extend for this purpose then the simplified one you propose. After trying this out I'd be happy to simplify the LLVM binding if we stick with the current approach of generating LLVM assembly and calling the tools.


Some of the cleanups and optimisations are quite significant. Highlights:

* I think the module LlvmCodeGen.Regs can mostly go away.
* There are some obvious representation changes that would improve
performance (String -> FastString, [a] -> OrdList a).

Review key:

XXX This needs to be addressed before the patch goes in
CLEAN A potential cleanup (some of these are quite major)
OPT A possible optimisation

Patch review follows:

hunk ./compiler/ghc.cabal.in 44
+Flag llvm
+ Description: Build the LLVM code generator.
+ Default: False
+ Manual: True

CLEAN Is there a good reason to want to disable the LLVM support, or
can it always be compiled in?

Since the LLVM back-end requires TNTC to be disabled, yes it should be disable by default.


+Flag unreg
+ Description: Build an unregistered version.
+ Default: False
+ Manual: True
+

XXX Is this necessary? As far as I'm aware an unregisterised build
currently works.

hunk ./compiler/ghc.cabal.in 101
+ if flag(llvm)
+ CPP-Options: -DLLVM
+ if flag(unreg)
+ CPP-Options: -DNO_REGS -DUSE_MINIINTERPRETER

XXX Why is this necessary? These CPP flags are added by GHC itself
(StaticFlagParser.unregFlags).

I did this at the time as I was finding that unregistered builds of GHC still used the BaseReg. All other registers were disabled but the BaseReg was still being used.


+type LMString = String

OPT You probably want to use something better than String, perhaps
FastString.

+-- | Llvm variables
+data LlvmVar
+ -- references to variables with a global scope.
+ = LMGlobalVar LMString LlvmType LlvmLinkageType
+ -- references to variables local for a function or parameters.
+ | LMLocalVar LMString LlvmType
+ -- a constant variable
+ | LMLitVar LlvmLit

OPT Rather than LMString in LMLocalVar, probably Unique would be
better. I think you always generate these from a Unique (but I could
be wrong) in which case it would be better to do that conversion when
printing. I'm not sure whether this applies to LMGlobalVar or not.


Yes except for one case. The STG virtual registers names are hard coded. E.g

--------
define fastcc void @Main_main2_entry(i32 %stg_terei_baseArg,i32 %stg_terei_spArg,i32 %stg_terei_hpArg,i32 %stg_terei_r1Arg) nounwind
{
cLD:
    %stg_terei_baseReg = alloca i32, i32 1
    %stg_terei_spReg = alloca i32, i32 1
    %stg_terei_hpReg = alloca i32, i32 1
    %stg_terei_r1Reg = alloca i32, i32 1
    store i32 %stg_terei_baseArg, i32* %stg_terei_baseReg
    store i32 %stg_terei_spArg, i32* %stg_terei_spReg
    store i32 %stg_terei_hpArg, i32* %stg_terei_hpReg
    store i32 %stg_terei_r1Arg, i32* %stg_terei_r1Reg
--------

Although this can be handled very easily.

+ deriving (Eq)
+fixAssignsTop :: RawCmmTop -> UniqSM RawCmmTop
+
+fixAssignsTop top@(CmmData _ _) = returnUs top
+
+fixAssignsTop (CmmProc info lbl params (ListGraph blocks)) =
+ mapUs fixAssignsBlock blocks `thenUs` \ blocks' ->
+ returnUs (CmmProc info lbl params (ListGraph blocks'))
+

CLEAN I think your local fixAssigns can go away (see comment with
LlvmCodeGen.Regs below): use the one from the NCG.

+cmmToCmm :: RawCmmTop -> RawCmmTop
+cmmToCmm top@(CmmData _ _) = top
+cmmToCmm (CmmProc info lbl params (ListGraph blocks)) =
+ let blocks' = map cmmBlockConFold (cmmMiniInline blocks)
+ blocks'' = map cmmAddReturn blocks'
+ in CmmProc info lbl params (ListGraph $ blocks'')
+

CLEAN I think your local cmmToCmm can go away (see comment with
LlvmCodeGen.Regs below): use the one from the NCG. We should also
look into not doing any optimisation at the C-- level at all, since
LLVM will do it all, however we do need to turn GlobalRegs into
BaseReg offsets where necessary, which is done by cmmToCmm.

Sure. I just copied the code from the NCG originally as I wanted to keep my work as self contained as possible to avoid any issues with tracking GHC head. Most the changes you suggest are ones that I was aware of but my guiding principle was that developer time was much more important then compile time due to me having a hard deadline for the work.


+type LlvmEnvMap = Map.Map LMString LlvmType

OPT A Map of Strings is very inefficient compared with a UniqFM of
FastStrings.

+type StmtData = (LlvmEnv, [LlvmStatement], [LlvmCmmTop])

OPT Use OrdList rather than lists here, as you're doing a lot of
appending. Append is O(1) in OrdList, O(n) with lists.

+type ExprData = (LlvmEnv, LlvmVar, LlvmStatements, [LlvmCmmTop])

OPT Again, LlvmStatements should probably be an OrdList.

Yep. Thought this was the case but went with what I knew for developer speed.


addfile ./compiler/llvmGen/LlvmCodeGen/Regs.hs
hunk ./compiler/llvmGen/LlvmCodeGen/Regs.hs 1
+--
----------------------------------------------------------------------------

+-- Deal with Cmm registers
+--
+-- Specifically, force use of register table (in memory), not pinned
+-- hardware registers as the LLVM back-end doesn't support this.
+--
+
+module LlvmCodeGen.Regs (
+
+ RealReg, realRegsOrdered, getRealRegReg, getRealRegArg, getGlobalRegAddr
+
+ ) where

CLEAN Unless I'm mistaken, most of this module can go away.

1. Use fixAssigns from the NCG.
2. Print out GlobalRegs as "stg_whatever..."

Then you don't need to bake in the register mapping (a maintenance
headache), and a lot of this code can go away: the RealReg type and
everything using it.


I have to think about this one. Regs can defiantly be cleaned up, no question I'm just not sure about removing RealReg. Its purpose right now is three things:

1) 'getGlobalRegAddr' makes STG registers into real registers or table offsets.

2) STG registers as said have hard coded names in the code the LLVM back-end generates. 'getRealRegReg', 'getRealRegArg'. These methods return the correctly named LLVM local register for a particular STG register.

3) realRegsOrdered encodes the calling convention for this target.

E.g for x86-32 = [RR_Base, RR_Sp, RR_Hp, RR_R1].

This encodes the number and order of the registers which are part of the calling convention. Here is the LLVM code for x86-32

CCIfType<[i32], CCAssignToReg<[EBX, EBP, EDI, ESI]>>,

So its quite simple really, just the number of registers pinned and the order they should be used as arguments.

The first two purposes can be removed. I'm just not so sure about the third at the moment. Will look into this more, have to check what's already provided by NCG again.


addfile ./compiler/llvmGen/NOTES
hunk ./compiler/llvmGen/NOTES 1
+LLVM Back-end for GHC.
+
+Author: David Terei

CLEAN Useful-looking docs. I suggest moving them into either (a) the
wiki commentary or (b) the code as appropriate.

hunk ./compiler/main/CodeOutput.lhs 16
+#ifdef LLVM
+#ifdef OMIT_NATIVE_CODEGEN
+import UniqSupply ( mkSplitUniqSupply )
+#endif
+import qualified LlvmCodeGen ( llvmCodeGen )
+#endif
+
hunk ./compiler/main/CodeOutput.lhs 90
+ HscLlvm -> outputLlvm dflags filenm flat_abstractC;
hunk ./compiler/main/CodeOutput.lhs 176
+%************************************************************************
+%* *
+\subsection{LLVM}
+%* *
+%************************************************************************
+
+\begin{code}
+outputLlvm :: DynFlags -> FilePath -> [RawCmm] -> IO ()
+
+#ifdef LLVM
+
+outputLlvm dflags filenm flat_absC
+ = do ncg_uniqs <- mkSplitUniqSupply 'n'
+ doOutput filenm $ \f ->
+ LlvmCodeGen.llvmCodeGen dflags f ncg_uniqs flat_absC
+
+#else /* !LLVM */

CLEAN suggest removing the #ifdefs and enabling LLVM unconditionally, as
above.

As above, TNTC problem means LLVM should be disabled by default.

Thanks for the feedback, will start working on this when I have time, away this weekend so I expect will take to the weekend following or so.

Cheers,
David

_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to