#1992: 6.8.2 intermittent build failure on multiple OS X versions
----------------------+-----------------------------------------------------
 Reporter:  guest     |          Owner:          
     Type:  bug       |         Status:  new     
 Priority:  normal    |      Milestone:  6.8.3   
Component:  Compiler  |        Version:  6.8.2   
 Severity:  normal    |     Resolution:          
 Keywords:            |     Difficulty:  Unknown 
 Testcase:            |   Architecture:  Multiple
       Os:  MacOS X   |  
----------------------+-----------------------------------------------------
Comment (by gw):

 Some progress:

 There are two distinct bugs here.  The problem with apparently failed
 ranlibs (or ld
 not determining if an archive has a table of contents) has been fixed by
 Apple's 10.5.2
 update.  I guess this is what the release note item "improved stability
 for third
 party applications" meant.  This bug was only seen on Leopard.

 This leaves only the locking bug.  A Macports build of 6.8.2 still fails
 because
 .depend-BASE appears to be locked (perhaps a race that allows the file
 descriptor
 to be reused by ghc before the file is unlocked):

 {{{
 ../utils/ghc-pkg/ghc-pkg-inplace update - --force-files
 <package.conf.inplace
 WARNING: unversioned dependencies are deprecated, and will NOT be accepted
 by GHC 6.10: hpc bytestring template-haskell readline unix Cabal base
 haskell98
 Reading package info from stdin ... done.
 cannot find libHSghc.a on library path (ignoring)
 Saving old package config file... done.
 Writing new package config file... done.
 Creating stage1/ghc_boot_platform.h...
 Done.
 touch .depend-BASE
 ../compiler/stage1/ghc-inplace -M -optdep-f -optdep.depend-BASE  -osuf o
 -I../includes   -H16m -O -I/opt/local/include -L/opt/local/lib -iutils
 -ibasicTypes -itypes -ihsSyn -iprelude -irename -itypecheck -ideSugar
 -icoreSyn -ivectorise -ispecialise -isimplCore -istranal -istgSyn
 -isimplStg -icodeGen -imain -iprofiling -iparser -icprAnalysis
 -indpFlatten -iiface -icmm -inativeGen -ighci -Wall -fno-warn-name-
 shadowing -fno-warn-orphans -Istage2 -package hpc -package bytestring
 -DGHCI -package template-haskell -DGHCI_TABLES_NEXT_TO_CODE -package
 readline -DUSE_READLINE -cpp -fglasgow-exts -fno-generics -Rghc-timing -I.
 -Iparser -package unix -package Cabal -ignore-package lang -recomp -Rghc-
 timing -H16M '-#include "cutils.h"' -package-name ghc-6.8.2 -fgenerics
 basicTypes/BasicTypes.lhs basicTypes/DataCon.lhs basicTypes/Demand.lhs
 basicTypes/Id.lhs basicTypes/IdInfo.lhs basicTypes/Literal.lhs
 basicTypes/MkId.lhs basicTypes/Module.lhs basicTypes/Name.lhs
 basicTypes/NameEnv.lhs basicTypes/NameSet.lhs basicTypes/NewDemand.lhs
 basicTypes/OccName.lhs basicTypes/RdrName.lhs basicTypes/SrcLoc.lhs
 basicTypes/UniqSupply.lhs basicTypes/Unique.lhs basicTypes/Var.lhs
 basicTypes/VarEnv.lhs basicTypes/VarSet.lhs cmm/CLabel.hs cmm/Cmm.hs
 cmm/CmmBrokenBlock.hs cmm/CmmCPS.hs cmm/CmmCPSGen.hs cmm/CmmCallConv.hs
 cmm/CmmInfo.hs cmm/CmmLex.hs cmm/CmmLint.hs cmm/CmmLive.hs cmm/CmmOpt.hs
 cmm/CmmParse.hs cmm/CmmProcPoint.hs cmm/CmmUtils.hs cmm/Dataflow.hs
 cmm/MachOp.hs cmm/PprC.hs cmm/PprCmm.hs codeGen/Bitmap.hs
 codeGen/CgBindery.lhs codeGen/CgCallConv.hs codeGen/CgCase.lhs
 codeGen/CgClosure.lhs codeGen/CgCon.lhs codeGen/CgExpr.lhs
 codeGen/CgForeignCall.hs codeGen/CgHeapery.lhs codeGen/CgHpc.hs
 codeGen/CgInfoTbls.hs codeGen/CgLetNoEscape.lhs codeGen/CgMonad.lhs
 codeGen/CgParallel.hs codeGen/CgPrimOp.hs codeGen/CgProf.hs
 codeGen/CgStackery.lhs codeGen/CgTailCall.lhs codeGen/CgTicky.hs
 codeGen/CgUtils.hs codeGen/ClosureInfo.lhs codeGen/CodeGen.lhs
 codeGen/SMRep.lhs coreSyn/CoreFVs.lhs coreSyn/CoreLint.lhs
 coreSyn/CorePrep.lhs coreSyn/CoreSubst.lhs coreSyn/CoreSyn.lhs
 coreSyn/CoreTidy.lhs coreSyn/CoreUnfold.lhs coreSyn/CoreUtils.lhs
 coreSyn/ExternalCore.lhs coreSyn/MkExternalCore.lhs coreSyn/PprCore.lhs
 coreSyn/PprExternalCore.lhs cprAnalysis/CprAnalyse.lhs deSugar/Check.lhs
 deSugar/Coverage.lhs deSugar/Desugar.lhs deSugar/DsArrows.lhs
 deSugar/DsBinds.lhs deSugar/DsCCall.lhs deSugar/DsExpr.lhs
 deSugar/DsForeign.lhs deSugar/DsGRHSs.lhs deSugar/DsListComp.lhs
 deSugar/DsMeta.hs deSugar/DsMonad.lhs deSugar/DsUtils.lhs
 deSugar/Match.lhs deSugar/MatchCon.lhs deSugar/MatchLit.lhs
 ghci/ByteCodeAsm.lhs ghci/ByteCodeFFI.lhs ghci/ByteCodeGen.lhs
 ghci/ByteCodeInstr.lhs ghci/ByteCodeItbls.lhs ghci/ByteCodeLink.lhs
 ghci/Debugger.hs ghci/GhciMonad.hs ghci/GhciTags.hs ghci/InteractiveUI.hs
 ghci/Linker.lhs ghci/ObjLink.lhs ghci/RtClosureInspect.hs
 hsSyn/Convert.lhs hsSyn/HsBinds.lhs hsSyn/HsDecls.lhs hsSyn/HsDoc.hs
 hsSyn/HsExpr.lhs hsSyn/HsImpExp.lhs hsSyn/HsLit.lhs hsSyn/HsPat.lhs
 hsSyn/HsSyn.lhs hsSyn/HsTypes.lhs hsSyn/HsUtils.lhs iface/BinIface.hs
 iface/BuildTyCl.lhs iface/IfaceEnv.lhs iface/IfaceSyn.lhs
 iface/IfaceType.lhs iface/LoadIface.lhs iface/MkIface.lhs
 iface/TcIface.lhs main/BreakArray.hs main/CmdLineParser.hs
 main/CodeOutput.lhs main/Config.hs main/Constants.lhs
 main/DriverMkDepend.hs main/DriverPhases.hs main/DriverPipeline.hs
 main/DynFlags.hs main/ErrUtils.lhs main/Finder.lhs main/GHC.hs
 main/HeaderInfo.hs main/HscMain.lhs main/HscStats.lhs main/HscTypes.lhs
 main/InteractiveEval.hs main/Main.hs main/PackageConfig.hs
 main/Packages.lhs main/ParsePkgConf.hs main/PprTyThing.hs
 main/StaticFlags.hs main/SysTools.lhs main/TidyPgm.lhs
 nativeGen/AsmCodeGen.lhs nativeGen/GraphBase.hs nativeGen/GraphColor.hs
 nativeGen/GraphOps.hs nativeGen/GraphPpr.hs nativeGen/MachCodeGen.hs
 nativeGen/MachInstrs.hs nativeGen/MachRegs.lhs nativeGen/NCGMonad.hs
 nativeGen/PositionIndependentCode.hs nativeGen/PprMach.hs
 nativeGen/RegAllocColor.hs nativeGen/RegAllocInfo.hs
 nativeGen/RegAllocLinear.hs nativeGen/RegAllocStats.hs
 nativeGen/RegArchBase.hs nativeGen/RegArchX86.hs nativeGen/RegCoalesce.hs
 nativeGen/RegLiveness.hs nativeGen/RegSpill.hs nativeGen/RegSpillClean.hs
 nativeGen/RegSpillCost.hs ndpFlatten/FlattenInfo.hs
 ndpFlatten/FlattenMonad.hs ndpFlatten/Flattening.hs
 ndpFlatten/NDPCoreUtils.hs ndpFlatten/PArrAnal.hs parser/Ctype.lhs
 parser/HaddockLex.hs parser/HaddockParse.hs parser/HaddockUtils.hs
 parser/LexCore.hs parser/Lexer.hs parser/Parser.hs parser/ParserCore.hs
 parser/ParserCoreUtils.hs parser/RdrHsSyn.lhs prelude/ForeignCall.lhs
 prelude/PrelInfo.lhs prelude/PrelNames.lhs prelude/PrelRules.lhs
 prelude/PrimOp.lhs prelude/TysPrim.lhs prelude/TysWiredIn.lhs
 profiling/CostCentre.lhs profiling/SCCfinal.lhs rename/RnBinds.lhs
 rename/RnEnv.lhs rename/RnExpr.lhs rename/RnHsDoc.hs rename/RnHsSyn.lhs
 rename/RnNames.lhs rename/RnSource.lhs rename/RnTypes.lhs
 simplCore/CSE.lhs simplCore/FloatIn.lhs simplCore/FloatOut.lhs
 simplCore/LiberateCase.lhs simplCore/OccurAnal.lhs simplCore/SAT.lhs
 simplCore/SATMonad.lhs simplCore/SetLevels.lhs simplCore/SimplCore.lhs
 simplCore/SimplEnv.lhs simplCore/SimplMonad.lhs simplCore/SimplUtils.lhs
 simplCore/Simplify.lhs simplStg/SRT.lhs simplStg/SimplStg.lhs
 simplStg/StgStats.lhs specialise/Rules.lhs specialise/SpecConstr.lhs
 specialise/Specialise.lhs stgSyn/CoreToStg.lhs stgSyn/StgLint.lhs
 stgSyn/StgSyn.lhs stranal/DmdAnal.lhs stranal/SaAbsInt.lhs
 stranal/SaLib.lhs stranal/StrictAnal.lhs stranal/WorkWrap.lhs
 stranal/WwLib.lhs typecheck/FamInst.lhs typecheck/Inst.lhs
 typecheck/TcArrows.lhs typecheck/TcBinds.lhs typecheck/TcClassDcl.lhs
 typecheck/TcDefaults.lhs typecheck/TcDeriv.lhs typecheck/TcEnv.lhs
 typecheck/TcExpr.lhs typecheck/TcForeign.lhs typecheck/TcGadt.lhs
 typecheck/TcGenDeriv.lhs typecheck/TcHsSyn.lhs typecheck/TcHsType.lhs
 typecheck/TcInstDcls.lhs typecheck/TcMType.lhs typecheck/TcMatches.lhs
 typecheck/TcPat.lhs typecheck/TcRnDriver.lhs typecheck/TcRnMonad.lhs
 typecheck/TcRnTypes.lhs typecheck/TcRules.lhs typecheck/TcSimplify.lhs
 typecheck/TcSplice.lhs typecheck/TcTyClsDecls.lhs typecheck/TcTyDecls.lhs
 typecheck/TcTyFuns.lhs typecheck/TcType.lhs typecheck/TcUnify.lhs
 types/Class.lhs types/Coercion.lhs types/FamInstEnv.lhs types/FunDeps.lhs
 types/Generics.lhs types/InstEnv.lhs types/TyCon.lhs types/Type.lhs
 types/TypeRep.lhs types/Unify.lhs utils/Bag.lhs utils/Binary.hs
 utils/BufWrite.hs utils/Digraph.lhs utils/Encoding.hs utils/FastMutInt.lhs
 utils/FastString.lhs utils/FastTypes.lhs utils/FiniteMap.lhs
 utils/IOEnv.hs utils/ListSetOps.lhs utils/Maybes.lhs utils/OrdList.lhs
 utils/Outputable.lhs utils/Panic.lhs utils/Pretty.lhs utils/State.hs
 utils/StringBuffer.lhs utils/UniqFM.lhs utils/UniqSet.lhs utils/Util.lhs
 vectorise/VectBuiltIn.hs vectorise/VectCore.hs vectorise/VectMonad.hs
 vectorise/VectType.hs vectorise/VectUtils.hs vectorise/Vectorise.hs
 .depend-BASE: openFile: resource busy (file is locked)
 <<ghc: 475635736 bytes, 81 GCs, 4911104/12984320 avg/max bytes residency
 (5 samples), 27M in use, 0.00 INIT (0.00 elapsed), 0.86 MUT (7.97
 elapsed), 0.14 GC (0.15 elapsed) :ghc>>
 make[2]: *** [depend] Error 1
 make[1]: *** [stage2] Error 2
 make: *** [bootstrap2] Error 2

 Warning: the following items did not execute (for ghc):
 org.macports.destroot org.macports.build
 Error: Status 1 encountered during processing.
 }}}

 As I noted before, the locking bug showed up on Tiger, so it is very
 likely
 a ghc problem.

 I am still puzzled by the fact that this bug doesn't seem to happen when I
 run
 make under bash in a terminal window.  Building under Macports tickles the
 bug, though.

-- 
Ticket URL: <http://hackage.haskell.org/trac/ghc/ticket/1992#comment:5>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
_______________________________________________
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs

Reply via email to