I managed to create an unregistered build that compiles the hello world example.
# file hello
hello: ELF 64-bit LSB executable, AMD x86-64, version 1 (SYSV), for GNU/Linux 2.6.0, dynamically linked (uses shared libs), not stripped


But when I tried to build a registered compiler with it (by using a fresh source tree with --with-ghc=ghc-test2/ghc-6.2.20040613/ghc/compiler/ghc-inplace), the "internal compiler error" occurred again. Is there a way to find out _why_ this happens?
regards
------------------------------------------------------------------------
==fptools== make boot -wr;
in ghc-test2/ghc-6.2.20040613/ghc/compiler
------------------------------------------------------------------------
../../glafp-utils/mkdirhier/mkdirhier stage1
for i in utils basicTypes types hsSyn prelude rename typecheck deSugar coreSyn specialise simplCore stranal stgSyn simplStg codeGen absCSyn main profiling parser cprAnalysis compMan ndpFlatten cbits; do \
../../glafp-utils/mkdirhier/mkdirhier stage1/$i; \
done
for i in */*hi-boot*; do \
ln -s -f ../../$i stage1/$i || true ; \
done
ln: creating symbolic link `stage1/nativeGen/MachMisc.hi-boot' to `../../nativeGen/MachMisc.hi-boot': No such file or directory
ln: creating symbolic link `stage1/nativeGen/MachMisc.hi-boot-5' to `../../nativeGen/MachMisc.hi-boot-5': No such file or directory
ln: creating symbolic link `stage1/nativeGen/MachMisc.hi-boot-6' to `../../nativeGen/MachMisc.hi-boot-6': No such file or directory
ln: creating symbolic link `stage1/nativeGen/Stix.hi-boot' to `../../nativeGen/Stix.hi-boot': No such file or directory
ln: creating symbolic link `stage1/nativeGen/StixPrim.hi-boot' to `../../nativeGen/StixPrim.hi-boot': No such file or directory
ln: creating symbolic link `stage1/nativeGen/StixPrim.hi-boot-5' to `../../nativeGen/StixPrim.hi-boot-5': No such file or directory
ln: creating symbolic link `stage1/nativeGen/StixPrim.hi-boot-6' to `../../nativeGen/StixPrim.hi-boot-6': No such file or directory
touch .depend-BASE
ghc-test2/ghc-6.2.20040613/ghc/compiler/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 -iabsCSyn -imain -iprofiling -iparser -icprAnalysis -icompMan -indpFlatten -icbits -DOMIT_NATIVE_CODEGEN -cpp -fglasgow-exts -Rghc-timing -I. -IcodeGen -InativeGen -Iparser -recomp -Rghc-timing -H16M '-#include "hschooks.h"' absCSyn/AbsCSyn.lhs absCSyn/AbsCUtils.lhs absCSyn/CLabel.lhs absCSyn/CStrings.lhs absCSyn/Costs.lhs absCSyn/MachOp.hs absCSyn/PprAbsC.lhs basicTypes/BasicTypes.lhs basicTypes/DataCon.lhs basicTypes/Demand.lhs basicTypes/FieldLabel.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 codeGen/Bitmap.hs codeGen/CgBindery.lhs codeGen/CgCase.lhs codeGen/CgClosure.lhs codeGen/CgCon.lhs codeGen/CgConTbls.lhs codeGen/CgExpr.lhs codeGen/CgHeapery.lhs codeGen/CgLetNoEscape.lhs codeGen/CgMonad.lhs codeGen/CgRetConv.lhs codeGen/CgStackery.lhs codeGen/CgTailCall.lhs codeGen/CgUpdate.lhs codeGen/CgUsages.lhs codeGen/ClosureInfo.lhs codeGen/CodeGen.lhs codeGen/SMRep.lhs compMan/CompManager.lhs coreSyn/CoreFVs.lhs coreSyn/CoreLint.lhs coreSyn/CorePrep.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 coreSyn/Subst.lhs cprAnalysis/CprAnalyse.lhs deSugar/Check.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/HsCore.lhs hsSyn/HsDecls.lhs hsSyn/HsExpr.lhs hsSyn/HsImpExp.lhs hsSyn/HsLit.lhs hsSyn/HsPat.lhs hsSyn/HsSyn.lhs hsSyn/HsTypes.lhs main/BinIface.hs main/CmdLineOpts.lhs main/CodeOutput.lhs main/Config.hs main/Constants.lhs main/DriverFlags.hs main/DriverMkDepend.hs main/DriverPhases.hs main/DriverPipeline.hs main/DriverState.hs main/DriverUtil.hs main/ErrUtils.lhs main/Finder.lhs main/GetImports.hs main/HscMain.lhs main/HscStats.lhs main/HscTypes.lhs main/Interpreter.hs main/Main.hs main/MkIface.lhs main/Packages.lhs main/ParsePkgConf.hs main/SysTools.lhs main/TidyPgm.lhs ndpFlatten/FlattenInfo.hs ndpFlatten/FlattenMonad.hs ndpFlatten/Flattening.hs ndpFlatten/NDPCoreUtils.hs ndpFlatten/PArrAnal.hs parser/Ctype.lhs 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/PrimRep.lhs prelude/TysPrim.lhs prelude/TysWiredIn.lhs profiling/CostCentre.lhs profiling/SCCfinal.lhs rename/RnBinds.lhs rename/RnEnv.lhs rename/RnExpr.lhs rename/RnHiFiles.lhs rename/RnHsSyn.lhs rename/RnIfaces.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/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/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/TcGenDeriv.lhs typecheck/TcHsSyn.lhs typecheck/TcIfaceSig.lhs typecheck/TcInstDcls.lhs typecheck/TcMType.lhs typecheck/TcMatches.lhs typecheck/TcMonoType.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/TcType.lhs typecheck/TcUnify.lhs types/Class.lhs types/FunDeps.lhs types/Generics.lhs types/InstEnv.lhs types/PprType.lhs types/TyCon.lhs types/Type.lhs types/TypeRep.lhs types/Variance.lhs utils/Bag.lhs utils/Binary.hs utils/BitSet.lhs utils/Digraph.lhs utils/FastMutInt.lhs utils/FastString.lhs utils/FastTypes.lhs utils/FiniteMap.lhs utils/ListSetOps.lhs utils/Maybes.lhs utils/OrdList.lhs utils/Outputable.lhs utils/Panic.lhs utils/Pretty.lhs utils/PrimPacked.lhs utils/StringBuffer.lhs utils/UnicodeUtil.lhs utils/UniqFM.lhs utils/UniqSet.lhs utils/Util.lhs
/tmp/ghc7353.lpp:0: internal compiler error: Aborted
Please submit a full bug report,
with preprocessed source if appropriate.
See <URL:http://bugs.gentoo.org/> for instructions.
<<ghc: 16575888 bytes, 5 GCs, 180224/180224 avg/max bytes residency (1 samples), 16M in use, 0.00 INIT (0.00 elapsed), 0.07 MUT (0.20 elapsed), 0.01 GC (0.04 elapsed) :ghc>>
make[2]: *** [depend] Error 1
make[1]: *** [boot] Error 1
make[1]: Leaving directory `ghc-test2/ghc-6.2.20040613/ghc'
make: *** [build] Error 1



Simon Marlow wrote:
On 16 June 2004 13:19, Gerd M wrote:

> Simon Marlow wrote:
>> It looks like HC bootstrapping is enabled in this tree; it shouldn't
>> be. Just use a completely fresh source tree, don't configure with
>> --enable-hc-boot, and don't unpack any HC files into it.
>>
> If I use a fresh source tree without HCs then I need the unregistered
> build to compile, right? Unfortunately the debian build didn't get me
> very far since it stops with an internal compiler error (see previous
> posts).

There seems to be some confusion.  The instructions I gave were for
Bennett, who said he had a working unregisterised build.  If you haven't
got that far yet, then these instructions don't apply.

> So I followed the instructions of the Porting Guide
> and compiled a ghc-6.2.1-x86_64_unknown_linux-hc.tar.gz in 32bit mode.
>
> In 64bit mode:
> ./distrib/hc-build --enable-hc-boot-unregisterised
> which stops with the error message I mentioned in my last post.
>> multiple definition of `forkOS_entry'
>> Control/Concurrent_stub.o(.text+0x0): first defined here

Don S. committed a fix for this to the main tree.  It looks like it
hasn't been merged yet... could you try the attached patch to
libraries/base/Makefile, and let me now if it helps?

Cheers,
        Simon

<< patch >>

_________________________________________________________________
The new MSN 8: advanced junk mail protection and 2 months FREE* http://join.msn.com/?page=features/junkmail


_______________________________________________
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Reply via email to