Fortunately I have ZipCfg on my disk and will push it in a sec. In Norman's defence, he's had a torrid time wrestling with darcs in the last week, and has been assiduously validating. Your advice is still absolutely valid though.
Simon | -----Original Message----- | From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Manuel M T | Chakravarty | Sent: 07 September 2007 06:27 | To: [email protected]; Norman Ramsey | Subject: The head is dead! | | I think Norman's mega patch broke the head. Error message appended. | It seems the ZipCfg module didn't get into the patch. | | Norman, I think it is good practise to use a repository separate | from your development repo for validating. This ensures that you | are testing what others get and not your local copy that possibly | contains files that are not under version control. See also | | http://hackage.haskell.org/trac/ghc/wiki/TestingPatches | | Manuel | | -=- | | /opt/local/bin/ghc -M -optdep-f -optdep.depend-BASE -osuf o | -I../includes -optdep--exclude-module=Compat.RawSystem | -optdep--exclude-module=Compat.Directory | -optdep--exclude-module=Compat.Unicode | -optdep--exclude-module=Distribution.Compat.FilePath | -optdep--exclude-module=Distribution.Compat.ReadP | -optdep--exclude-module=Distribution.Extension | -optdep--exclude-module=Distribution.GetOpt | -optdep--exclude-module=Distribution.InstalledPackageInfo | -optdep--exclude-module=Distribution.License | -optdep--exclude-module=Distribution.Package | -optdep--exclude-module=Distribution.ParseUtils | -optdep--exclude-module=Distribution.Compiler | -optdep--exclude-module=Distribution.Version | -optdep--exclude-module=System.FilePath | -optdep--exclude-module=System.FilePath.Posix | -optdep--exclude-module=System.FilePath.Windows | -optdep--exclude-module=System.Directory.Internals | -optdep--exclude-module=Trace.Hpc.Mix | -optdep--exclude-module=Trace.Hpc.Tix | -optdep--exclude-module=Trace.Hpc.Util -Werror -H64m -Onot -fasm | -iutils -ibasicTypes -itypes -ihsSyn -iprelude -irename -itypecheck | -ideSugar -icoreSyn -ivectorise -ispecialise -isimplCore -istranal | -istgSyn -isimplStg -icodeGen -imain -iprofiling -iparser | -icprAnalysis -indpFlatten -iiface -icmm -inativeGen -Wall | -fno-warn-name-shadowing -Istage1 -cpp -fglasgow-exts -fno-generics | -Rghc-timing -I. -Iparser -package unix -ignore-package lang -recomp | -Rghc-timing -O -fasm -H16M '-#include "cutils.h"' -DUSING_COMPAT | -i../compat -ignore-package Cabal 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/DsMonad.lhs | deSugar/DsUtils.lhs deSugar/Match.lhs deSugar/MatchCon.lhs | deSugar/MatchLit.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 | 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/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 | | cmm/Cmm.hs:60:7: | Could not find module `ZipCfg': | Use -v to see a list of the files searched for. | <<ghc: 317872184 bytes, 41 GCs, 3852962/9302316 avg/max bytes | residency (4 samples), 26M in use, 0.01 INIT (0.00 elapsed), 0.64 | MUT (9.39 elapsed), 0.08 GC (0.10 elapsed) :ghc>> | make[1]: *** [depend] Error 1 | make: *** [stage1] Error 1 | wireless-193 chak 34 (.../Code/ghc-test): | | _______________________________________________ | Cvs-ghc mailing list | [email protected] | http://www.haskell.org/mailman/listinfo/cvs-ghc _______________________________________________ Cvs-ghc mailing list [email protected] http://www.haskell.org/mailman/listinfo/cvs-ghc
