Ian,

Thank for doing this.  But please (as always) could you add add "Note 
[Generating fresh names for ccall wrapper]", refer to it in the code, and write 
a comment that explains why we are going to this trouble. (Refer to the Trac 
ticket.)

I do this EVERY time I fix a bug.  It saves me lots of time later.  I commend 
it to you.

Simon

|  -----Original Message-----
|  From: cvs-ghc-boun...@haskell.org [mailto:cvs-ghc-boun...@haskell.org] On
|  Behalf Of Ian Lynagh
|  Sent: 02 November 2012 16:09
|  To: cvs-ghc@haskell.org
|  Subject: [commit: ghc] master: Don't put uniqs in ghc wrapper function names;
|  part of #4012 (095b9bf)
|  
|  Repository : ssh://darcs.haskell.org//srv/darcs/ghc
|  
|  On branch  : master
|  
|  http://hackage.haskell.org/trac/ghc/changeset/095b9bf4ed418c43216cfca2ae271
|  c143e555f1d
|  
|  >---------------------------------------------------------------
|  
|  commit 095b9bf4ed418c43216cfca2ae271c143e555f1d
|  Author: Ian Lynagh <i...@well-typed.com>
|  Date:   Fri Nov 2 03:45:15 2012 +0000
|  
|      Don't put uniqs in ghc wrapper function names; part of #4012
|  
|      The wrapper functions can end up in interface files, and thus are
|      part of the ABI hash. But uniqs easily change for no good reason
|      when recompiling, which can lead to an ABI hash needlessly changing.
|  
|  >---------------------------------------------------------------
|  
|   compiler/deSugar/DsForeign.lhs |   20 +++++++++++++++-----
|   compiler/main/DynFlags.hs      |   11 ++++++++---
|   2 files changed, 23 insertions(+), 8 deletions(-)
|  
|  diff --git a/compiler/deSugar/DsForeign.lhs b/compiler/deSugar/DsForeign.lhs
|  index 0cf4b97..42aa740 100644
|  --- a/compiler/deSugar/DsForeign.lhs
|  +++ b/compiler/deSugar/DsForeign.lhs
|  @@ -44,10 +44,12 @@ import FastString
|   import DynFlags
|   import Platform
|   import Config
|  +import Encoding
|   import OrdList
|   import Pair
|   import Util
|  
|  +import Data.IORef
|   import Data.Maybe
|   import Data.List
|   \end{code}
|  @@ -211,11 +213,19 @@ dsFCall fn_id co fcall mDeclHeader = do
|       (fcall', cDoc) <-
|                 case fcall of
|                 CCall (CCallSpec (StaticTarget cName mPackageId isFun) 
CApiConv
|  safety) ->
|  -               do fcall_uniq <- newUnique
|  -                  let wrapperName = mkFastString "ghc_wrapper_" `appendFS`
|  -                                    mkFastString (showPpr dflags 
fcall_uniq) `appendFS`
|  -                                    mkFastString "_" `appendFS`
|  -                                    cName
|  +               do let wrapperRef = nextWrapperNum dflags
|  +                  wrapperNum <- liftIO $ readIORef wrapperRef
|  +                  liftIO $ writeIORef wrapperRef (wrapperNum + 1)
|  +                  thisMod <- getModuleDs
|  +                  let pkg = packageIdString  (modulePackageId thisMod)
|  +                      mod = moduleNameString (moduleName      thisMod)
|  +                      wrapperNameComponents = ["ghc_wrapper",
|  +                                               show wrapperNum,
|  +                                               pkg, mod,
|  +                                               unpackFS cName]
|  +                      wrapperName = mkFastString
|  +                                  $ zEncodeString
|  +                                  $ intercalate ":" wrapperNameComponents
|                         fcall' = CCall (CCallSpec (StaticTarget wrapperName 
mPackageId
|  True) CApiConv safety)
|                         c = includes
|                          $$ fun_proto <+> braces (cRet <> semi)
|  diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
|  index 4810ce8..07ebd40 100644
|  --- a/compiler/main/DynFlags.hs
|  +++ b/compiler/main/DynFlags.hs
|  @@ -690,7 +690,9 @@ data DynFlags = DynFlags {
|  
|     interactivePrint      :: Maybe String,
|  
|  -  llvmVersion           :: IORef (Int)
|  +  llvmVersion           :: IORef (Int),
|  +
|  +  nextWrapperNum        :: IORef Int
|    }
|  
|   class HasDynFlags m where
|  @@ -1111,12 +1113,14 @@ initDynFlags dflags = do
|    refFilesToNotIntermediateClean <- newIORef []
|    refGeneratedDumps <- newIORef Set.empty
|    refLlvmVersion <- newIORef 28
|  + wrapperNum <- newIORef 0
|    return dflags{
|           filesToClean   = refFilesToClean,
|           dirsToClean    = refDirsToClean,
|           filesToNotIntermediateClean = refFilesToNotIntermediateClean,
|           generatedDumps = refGeneratedDumps,
|  -        llvmVersion    = refLlvmVersion
|  +        llvmVersion    = refLlvmVersion,
|  +        nextWrapperNum = wrapperNum
|           }
|  
|   -- | The normal 'DynFlags'. Note that they is not suitable for use in this 
form
|  @@ -1239,7 +1243,8 @@ defaultDynFlags mySettings =
|           traceLevel = 1,
|           profAuto = NoProfAuto,
|           llvmVersion = panic "defaultDynFlags: No llvmVersion",
|  -        interactivePrint = Nothing
|  +        interactivePrint = Nothing,
|  +        nextWrapperNum = panic "defaultDynFlags: No nextWrapperNum"
|         }
|  
|   defaultWays :: Settings -> [Way]
|  
|  
|  
|  _______________________________________________
|  Cvs-ghc mailing list
|  Cvs-ghc@haskell.org
|  http://www.haskell.org/mailman/listinfo/cvs-ghc

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

Reply via email to