GHC 6.8.1 on powerpc OS X 10.5

Chris Kuklewicz haskell at list.mightyreason.com
Thu Nov 15 14:15:14 EST 2007


I have attacked ld64 from a different direction.  This is a long message, the
gist of which is that I have partly backtracked the "unknown scattered
relocation type 4" error message that is printed when compiling ghc-6.8.1

Topic: Why does ghc-6.8.1 fail on powerpc (G4 and G5) OS X 10.5 (Leopard) with
XCode 3.0 ?
(Bootstrapped with ghc-6.6.1 from OS 10.4 (Tiger))

obvious symptom: stage2 compiler segfaults, gdb reports:
> Program received signal SIGTRAP, Trace/breakpoint trap.
> 0x8fe0100c in __dyld__dyld_start ()

The main error seen is "unknown scattered relocation type 4" during
linking when building ghc.

I have gone digging into the source code of the linker to see what
causes this crytic message.  I pulled the source of ld from
http://www.opensource.apple.com/darwinsource/10.5/

The ld64-77.tar.gz package from apple has the message eminating from
./ld64-77/src/MachOReaderRelocatable.hpp

It can be produced by two lines:
pamac-cek10:src chrisk$ grep -C3 -nr "unknown scattered relocation type" .
./MachOReaderRelocatable.hpp-3162-				printf("unexpected scattered relocation
type PPC_RELOC_HI16_SECTDIFF\n");
./MachOReaderRelocatable.hpp-3163-				break;
./MachOReaderRelocatable.hpp-3164-			default:
./MachOReaderRelocatable.hpp:3165:				printf("unknown scattered relocation type
%d\n", sreloc->r_type());
./MachOReaderRelocatable.hpp-3166-		}
./MachOReaderRelocatable.hpp-3167-	}
./MachOReaderRelocatable.hpp-3168-	return result;
--
./MachOReaderRelocatable.hpp-3367-				// do nothing, already used via a look ahead
./MachOReaderRelocatable.hpp-3368-				break;
./MachOReaderRelocatable.hpp-3369-			default:
./MachOReaderRelocatable.hpp:3370:				printf("unknown scattered relocation type
%d\n", sreloc->r_type());
./MachOReaderRelocatable.hpp-3371-		}
./MachOReaderRelocatable.hpp-3372-	}
./MachOReaderRelocatable.hpp-3373-	return result;

I now need to figure out which line is responsible for the error.  It
turns out only one of the lines can print "4".

They are both the default case of switch statements:
egrep -n 'switch|case|default|unknown scattered relocation type'
MachOReaderRelocatable.hpp

3010:		switch (sreloc->r_type()) {
3011:			case PPC_RELOC_VANILLA:
3019:			case PPC_RELOC_BR14:
3030:			case PPC_RELOC_BR24:
3042:			case PPC_RELOC_LO16_SECTDIFF:
3054:			case PPC_RELOC_LO14_SECTDIFF:
3066:			case PPC_RELOC_HA16_SECTDIFF:
3078:			case PPC_RELOC_LO14:
3090:			case PPC_RELOC_LO16:
3102:			case PPC_RELOC_HA16:
3114:			case PPC_RELOC_SECTDIFF:
3115:			case PPC_RELOC_LOCAL_SECTDIFF:
3122:					switch ( sreloc->r_length() ) {
3123:						case 0:
3131:						case 1:
3139:						case 2:
3147:						case 3:
3159:			case PPC_RELOC_PAIR:
3161:			case PPC_RELOC_HI16_SECTDIFF:
3164:			default:
3165:				printf("unknown scattered relocation type %d\n", sreloc->r_type());


3307:		switch (sreloc->r_type()) {
3308:			case GENERIC_RELOC_VANILLA:
3323:			case GENERIC_RELOC_SECTDIFF:
3324:			case GENERIC_RELOC_LOCAL_SECTDIFF:
3332:					switch ( sreloc->r_length() ) {
3333:						case 0:
3334:						case 3:
3336:						case 1:
3340:						case 2:
3366:			case GENERIC_RELOC_PAIR:
3369:			default:
3370:				printf("unknown scattered relocation type %d\n", sreloc->r_type());

Where are these constants from?
The first switch statement uses constants from under /usr/include via
#include <mach-o/ppc/reloc.h>
enum reloc_type_ppc
{
    PPC_RELOC_VANILLA,  /* generic relocation as discribed above */
    PPC_RELOC_PAIR,     /* the second relocation entry of a pair */
    PPC_RELOC_BR14,     /* 14 bit branch displacement (to a word address) */
    PPC_RELOC_BR24,     /* 24 bit branch displacement (to a word address) */
    PPC_RELOC_HI16,     /* a PAIR follows with the low half */
    PPC_RELOC_LO16,     /* a PAIR follows with the high half */
    PPC_RELOC_HA16,     /* Same as the RELOC_HI16 except the low 16 bits and the
                         * high 16 bits are added together with the low 16 bits
                         * sign extened first.  This means if bit 15 of the low
                         * 16 bits is set the high 16 bits stored in the
                         * instruction will be adjusted.
                         */
    PPC_RELOC_LO14,     /* Same as the LO16 except that the low 2 bits are not
                         * stored in the instruction and are always zero.  This
                         * is used in double word load/store instructions.
                         */
    PPC_RELOC_SECTDIFF, /* a PAIR follows with subtract symbol value */
    PPC_RELOC_PB_LA_PTR,/* prebound lazy pointer */
    PPC_RELOC_HI16_SECTDIFF, /* section difference forms of above.  a PAIR */
    PPC_RELOC_LO16_SECTDIFF, /* follows these with subtract symbol value */
    PPC_RELOC_HA16_SECTDIFF,
    PPC_RELOC_JBSR,
    PPC_RELOC_LO14_SECTDIFF,
    PPC_RELOC_LOCAL_SECTDIFF  /* like PPC_RELOC_SECTDIFF, but the symbol
                                 referenced was local.  */
};

So here the 4th one is PPC_RELOC_HI16 and this is not handled in the first
switch statement!

The other switch is over /usr/include/mach-o/reloc.h 's :
enum reloc_type_generic
{
    GENERIC_RELOC_VANILLA,      /* generic relocation as discribed above */
    GENERIC_RELOC_PAIR,         /* Only follows a GENERIC_RELOC_SECTDIFF */
    GENERIC_RELOC_SECTDIFF,
    GENERIC_RELOC_PB_LA_PTR,    /* prebound lazy pointer */
    GENERIC_RELOC_LOCAL_SECTDIFF
};

Here the 4th value is GENERIC_RELOC_LOCAL_SECTDIFF.  This is handled
by the switch (though I note that GENERIC_RELOC_PB_LA_PTR is not
recognized).

Thus it looks like the error relates to the presence of PPC_RELOC_HI16
segments in the object files being linked by ld.  I will now look at
the rest of the ld code to see what does mention PPC_RELOC_HI16.

The PPC_RELOC_HI16 is handled in only one place in the
MachOReaderRelocatable.hpp file.  The handled and unhandled code paths
depend on the value of the "scattered" flag, and are different
branches of an if-else in the function:

bool Reader<A>::addRelocReference_powerpc(const macho_section<typename A::P>*
sect, const macho_relocation_info<typename A::P>* reloc)

There is an early if-else test (reloc->r_address() & R_SCATTERED) == 0
The R_SCATTERED is defined in /usr/include/reloc.h:
#define R_SCATTERED 0x80000000	/* mask to be applied to the r_address field
The rest of reloc.h defines the bit batterns that are abstracted by
the template classes MachOFileAbstraction.hpp which provide
r_address().  ( macho_relocation_info and
macho_scattered_relocation_info classes)

So it looks like the addRelocReference_powerpc cannot handle a
scattered PPC_RELOC_HI16 type.

Looking at the rest of the code, I see that MachOWriterExecutable.hpp
has a function:

template <typename A>
uint32_t Writer<A>::addObjectRelocs_powerpc(ObjectFile::Atom* atom,
ObjectFile::Reference* ref)

...which can create a type PPC_RELOC_HI16 with the scattered flag set
to true (see line 2904).  Thus it seems that the ld program has code
to create a situation (scattered is true && type is PPC_RELOC_HI16)
that it cannot handle.

This does not mean that ld is responsible for creating the scattered
PPC_RELOC_HI16.

And since I now know what to look for, I go digging with 'otool -r'
and 'otool -v -r' which quickly verifies that HI16 is type 4 and that
many of the ".o" files under
./ghc-6.8.1/libraries/base/dist/build
do have scattered HI16 relocations.

And now I need to quit this for tonight.


More information about the Glasgow-haskell-users mailing list