GHC 6.7 on OS X - Readline error
Deborah Goldsmith
dgoldsmith at mac.com
Wed May 23 21:48:59 EDT 2007
Did you point configure at where your readline library is installed,
as discussed on the below wiki page?
http://hackage.haskell.org/trac/ghc/wiki/Building/MacOSX
Deborah
On May 23, 2007, at 6:06 PM, Philip Weaver wrote:
> Hello all,
>
> My first email to this list, so I apologize if I don't ask my
> question appropriately...
>
> I have GHC 6.6 installed on an Intel Mac (Tiger 10.4), with the
> readline package installed and System.Console.Readline module
> working fine. However, when I try to build GHC 6.7 from source (I
> have tried many different nightly releases, and I have downloaded
> the extra-lib tarball as well), I always get an error message like
> this:
>
>
> ghci/InteractiveUI.hs:69:7:
> Could not find module `System.Console.Readline':
> Use -v to see a list of the files searched for.
> <<ghc: 304609140 bytes, 46 GCs, 4250800/9484772 avg/max bytes
> residency (4 samples), 26M in use, 0.01 INIT (0.00 elapsed), 0.66
> MUT (6.89 elapsed), 0.10 GC (0.11 elapsed) :ghc>>
> make[2]: *** [depend] Error 1
> make[1]: *** [stage2] Error 2
> make: *** [bootstrap2] Error 2
>
> I could not find any information about this on google, so I am
> posting here. Anyone know how to fix this? Thanks!
>
> Here's some more information if you need it. This is the command
> that the make file executed which failed:
>
> ../compiler/stage1/ghc-inplace -M -optdep-f -optdep.depend-BASE -
> osuf o -I../includes -H16m -O -iutils -ibasicTypes -itypes -
> ihsSyn -iprelude -irename -itypecheck -ideSugar -icoreSyn -
> ispecialise -isimplCore -istranal -istgSyn -isimplStg -icodeGen -
> imain -iprofiling -iparser -icprAnalysis -indpFlatten -iiface -icmm
> -inativeGen -ighci -Istage2 -DGHCI -package template-haskell -
> DDEBUGGER -DGHCI_TABLES_NEXT_TO_CODE -threaded -package readline -
> DUSE_READLINE -cpp -fglasgow-exts -fno-generics -Rghc-timing -I. -
> Iparser -package unix -package Cabal -package regex-compat -ignore-
> package lang -recomp -Rghc-timing -H16M '-#include " cutils.h"' -
> package-name ghc-6.7.20070330 -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/
> CmmLex.hs cmm/CmmLint.hs cmm/CmmOpt.hs cmm/CmmParse.hs cmm/
> CmmUtils.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/
> DsBreakpoint.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/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/
> Breakpoints.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/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/MachCodeGen.hs
> nativeGen/MachInstrs.hs nativeGen/MachRegs.lhs nativeGen/
> NCGMonad.hs nativeGen/PositionIndependentCode.hs nativeGen/
> PprMach.hs nativeGen/RegAllocInfo.hs nativeGen/RegisterAlloc.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/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/StringBuffer.lhs utils/UniqFM.lhs utils/
> UniqSet.lhs utils/Util.lhs
>
> - Phil
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/glasgow-haskell-users/attachments/20070523/9f390eaf/attachment.htm
More information about the Glasgow-haskell-users
mailing list