Package abi hash and interface file versions

Joachim Breitner nomeata at debian.org
Thu Jul 14 10:28:12 CEST 2011


Hi,

Am Mittwoch, den 13.07.2011, 14:09 +0200 schrieb Joachim Breitner:
> Even if you do not plan to support modules across minor versions of ghc,
> I’d like to get that into the hash. This would save us the trouble of
> tracking which package was built with what version of ghc and the same
> rebuild logic would apply that already handles the case of updated
> package dependencies.

looking at the code, all that is needed would be to modify this file in
ghc/Main.hs, and add something like the marked line to it (untested, as
I do not have a partial build lying around, and my machine sometimes
doesn’t take the heat from building ghc without crashing :-( ):

abiHash :: [(String, Maybe Phase)] -> Ghc ()
abiHash strs = do
  hsc_env <- getSession
  let dflags = hsc_dflags hsc_env

  liftIO $ do

  let find_it str = do
         let modname = mkModuleName str
         r <- findImportedModule hsc_env modname Nothing
         case r of
           Found _ m -> return m
           _error    -> ghcError $ CmdLineError $ showSDoc $
                          cannotFindInterface dflags modname r

  mods <- mapM find_it (map fst strs)

  let get_iface modl = loadUserInterface False (text "abiHash") modl
  ifaces <- initIfaceCheck hsc_env $ mapM get_iface mods

  bh <- openBinMem (3*1024) -- just less than a block
  put_ bh opt_HiVersion -- would adding this be sufficient
  mapM_ (put_ bh . mi_mod_hash) ifaces
  f <- fingerprintBinMem bh

  putStrLn (showSDoc (ppr f))


Haskell is currently broken in Debian on i386 and other arches and I’d
like to get this fix in quickly, but of course not without upstream
review.

Greetings,
Joachim
-- 
Joachim "nomeata" Breitner
Debian Developer
  nomeata at debian.org | ICQ# 74513189 | GPG-Keyid: 4743206C
  JID: nomeata at joachim-breitner.de | http://people.debian.org/~nomeata
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
URL: <http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20110714/e78f679b/attachment.pgp>


More information about the Glasgow-haskell-users mailing list