On Sat, 2010-01-02 at 00:03 +0100, Maxime Henrion wrote:
> On Wed, 2009-12-30 at 14:20 +0000, Duncan Coutts wrote:
> > On Wed, 2009-12-30 at 12:09 +0100, Maxime Henrion wrote:
> > 
> > > - Is there a plan to deal with the ldconfig cache on UNIX systems? As
> > > things are now, I had to manually add all the package directories
> > > under /usr/local/lib/ghc-6.12.1/ to be able to run the generated
> > > executable. I guess Cabal could produce a list of directories in some
> > > way for the system to do the right thing afterward, or we need some kind
> > > of a hack for setting LD_LIBRARY_PATH prior to starting the executable.
> > 
> > As Andrew says, we use -rpath on Linux for the "-dynload sysdep" mode.
> > This should also work on FreeBSD and other ELF platforms.
> 
> Thanks to both of you: that was it! I just had to handle a couple more
> '#ifdef linux_TARGET_OS' statements around the code implementing this
> -rpath feature.
> 
> > >  - I'm a bit surprised at the naming convention for the shared
> > > libraries. The library name includes both the package and the compiler
> > > versions, preventing any "automatic" upgrading.
> > 
> > Yes. They cannot be upgraded. They have no stable ABI. Achieving a
> > somewhat stable ABI may become possible in the future.
> > 
> > > If a new version of some package fixes bugs, improves performance,
> > > etc... but otherwise doesn't break the ABI, we are still going to be
> > > forced to rebuild binaries to take advantage of it.
> > 
> > Yes.
> > 
> > > Similarly if a new compiler version produces better code but doesn't
> > > break the ABI, but I'm less concerned about that one. I suppose an ABI
> > > number could be handled at the Cabal level, and only bumped when
> > > maintainers know it is appropriate, otherwise, we won't be getting one
> > > of the nice advantages of shared libraries.
> > 
> > The problem is that at the moment GHC cannot produce libs with a stable
> > ABI. Internal changes in a function can change the function's ABI. Up
> > until recently doing things like adding a non-exported function could
> > change IDs used in linker symbols.
> > 
> > Simon Marlow's plan is to do something like let people declare that a
> > package provides a certain ABI and then have the compiler shout at you
> > if you make changes that would change the ABI. That, along with other
> > changes like not exporting any unfoldings by default for stable ABI
> > modules, unless marked INLINE.
> 
> Thanks for the explanation.
> 
> I'm attaching an updated patch that defines the 'elf_TARGET_OS' macro
> when a target OS is known to support ELF-like shared libraries, and have
> used it wherever Linux & FreeBSD were matched previously. Now that I
> think about it, elf_TARGET_OS isn't such a great name since it's in the
> wrong namespace and would conflict with an OS named ELF. Quite unlikely,
> but still not pretty - something like elf_TARGET_LIBS is probably
> better.
> 
> I should do something similar for the runtime tests.
> 
> I have added the 'amd64-unknown-freebsd' platform to the list of
> platforms where we support shared libraries, since it should work just
> fine (testers would be great).
> 
> The -rpath feature (see above) now works properly on FreeBSD too.
> 
> The sed-related hack is also gone, thanks to an upstream change
> correcting the problem.
> 
> Any suggestions or comments about this patch would be greatly
> appreciated.
> 
> A happy new year to all the GHC users and developers!

Yet another update to this patch: similarly to how I have done with the
elf_TARGET_OS macro for compile-time decisions, I have added a new
osElfTarget predicate that indicates whether the OS supports ELF-like
shared libraries. I have updated all the code that was previously just
handling the OSLinux case in PIC.hs to use this function.

At that point I feel like this patch would be worth committing, minus
the libffi/ghc.mk hack and possibly name changes, so I'm even more eager
to hear about the advice of the GHC community.

Cheers,
Maxime
diff -rN -u old-ghc/compiler/HsVersions.h new-ghc/compiler/HsVersions.h
--- old-ghc/compiler/HsVersions.h	2010-01-03 23:07:51.000000000 +0100
+++ new-ghc/compiler/HsVersions.h	2010-01-03 23:07:55.000000000 +0100
@@ -16,6 +16,11 @@
 /* Pull in all the platform defines for this build (foo_TARGET_ARCH etc.) */
 #include "ghc_boot_platform.h"
 
+/* This macro indicates that the target OS supports ELF-like shared libraries */
+#if linux_TARGET_OS || freebsd_TARGET_OS
+#define elf_TARGET_OS 1
+#endif
+
 /* Pull in the autoconf defines (HAVE_FOO), but don't include
  * ghcconfig.h, because that will include ghcplatform.h which has the
  * wrong platform settings for the compiler (it has the platform
diff -rN -u old-ghc/compiler/cmm/CLabel.hs new-ghc/compiler/cmm/CLabel.hs
--- old-ghc/compiler/cmm/CLabel.hs	2010-01-03 23:07:51.000000000 +0100
+++ new-ghc/compiler/cmm/CLabel.hs	2010-01-03 23:07:55.000000000 +0100
@@ -1001,7 +1001,7 @@
 pprDynamicLinkerAsmLabel _ _
   = panic "pprDynamicLinkerAsmLabel"
 
-#elif powerpc_TARGET_ARCH && linux_TARGET_OS
+#elif powerpc_TARGET_ARCH && elf_TARGET_OS
 pprDynamicLinkerAsmLabel CodeStub lbl
   = pprCLabel lbl <> text "@plt"
 pprDynamicLinkerAsmLabel SymbolPtr lbl
@@ -1009,7 +1009,7 @@
 pprDynamicLinkerAsmLabel _ _
   = panic "pprDynamicLinkerAsmLabel"
 
-#elif x86_64_TARGET_ARCH && linux_TARGET_OS
+#elif x86_64_TARGET_ARCH && elf_TARGET_OS
 pprDynamicLinkerAsmLabel CodeStub lbl
   = pprCLabel lbl <> text "@plt"
 pprDynamicLinkerAsmLabel GotSymbolPtr lbl
@@ -1019,7 +1019,7 @@
 pprDynamicLinkerAsmLabel SymbolPtr lbl
   = text ".LC_" <> pprCLabel lbl
 
-#elif linux_TARGET_OS
+#elif elf_TARGET_OS
 pprDynamicLinkerAsmLabel CodeStub lbl
   = pprCLabel lbl <> text "@plt"
 pprDynamicLinkerAsmLabel SymbolPtr lbl
diff -rN -u old-ghc/compiler/main/DriverPipeline.hs new-ghc/compiler/main/DriverPipeline.hs
--- old-ghc/compiler/main/DriverPipeline.hs	2010-01-03 23:07:52.000000000 +0100
+++ new-ghc/compiler/main/DriverPipeline.hs	2010-01-03 23:07:56.000000000 +0100
@@ -1374,7 +1374,7 @@
 
     pkg_lib_paths <- getPackageLibraryPath dflags dep_packages
     let pkg_lib_path_opts = concat (map get_pkg_lib_path_opts pkg_lib_paths)
-#ifdef linux_TARGET_OS
+#ifdef elf_TARGET_OS
         get_pkg_lib_path_opts l | (dynLibLoader dflags)==SystemDependent && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l]
                                 | otherwise = ["-L" ++ l]
 #else
@@ -1573,7 +1573,7 @@
 #endif
     let pkg_lib_paths = collectLibraryPaths pkgs_no_rts
     let pkg_lib_path_opts = concatMap get_pkg_lib_path_opts pkg_lib_paths
-#ifdef linux_TARGET_OS
+#ifdef elf_TARGET_OS
         get_pkg_lib_path_opts l | (dynLibLoader dflags)==SystemDependent && not opt_Static = ["-L" ++ l, "-Wl,-rpath", "-Wl," ++ l]
                                 | otherwise = ["-L" ++ l]
 #else
diff -rN -u old-ghc/compiler/nativeGen/NCG.h new-ghc/compiler/nativeGen/NCG.h
--- old-ghc/compiler/nativeGen/NCG.h	2010-01-03 23:07:52.000000000 +0100
+++ new-ghc/compiler/nativeGen/NCG.h	2010-01-03 23:07:56.000000000 +0100
@@ -110,5 +110,11 @@
 #else
 # define IF_OS_darwin(x,y) y
 #endif
+-- - - - - - - - - - - - - - - - - - - - - - 
+#if freebsd_TARGET_OS
+# define IF_OS_freebsd(x,y) x
+#else
+# define IF_OS_freebsd(x,y) y
+#endif
 ---------------------------------------------
 #endif
diff -rN -u old-ghc/compiler/nativeGen/PIC.hs new-ghc/compiler/nativeGen/PIC.hs
--- old-ghc/compiler/nativeGen/PIC.hs	2010-01-03 23:07:52.000000000 +0100
+++ new-ghc/compiler/nativeGen/PIC.hs	2010-01-03 23:07:56.000000000 +0100
@@ -290,37 +290,38 @@
 -- from position independent code. It is also required from the main program
 -- when dynamic libraries containing Haskell code are used.
 
-howToAccessLabel _ ArchPPC_64 OSLinux kind _
+howToAccessLabel _ ArchPPC_64 os kind _
+	| osElfTarget os
+	= if kind == DataReference
+	    -- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
+            then AccessViaSymbolPtr
+	    -- actually, .label instead of label
+            else AccessDirectly
 
-	-- ELF PPC64 (powerpc64-linux), AIX, MacOS 9, BeOS/PPC
-	| DataReference	<- kind
-	= AccessViaSymbolPtr
-	
-	-- actually, .label instead of label
-	| otherwise
-	= AccessDirectly 
-
-howToAccessLabel _ _ OSLinux _ _
+howToAccessLabel _ _ os _ _
 	-- no PIC -> the dynamic linker does everything for us;
 	--           if we don't dynamically link to Haskell code,
 	--           it actually manages to do so without messing thins up.
-	| not opt_PIC && opt_Static 
+	| osElfTarget os
+	, not opt_PIC && opt_Static 
 	= AccessDirectly
 
-howToAccessLabel dflags arch OSLinux DataReference lbl
-	-- A dynamic label needs to be accessed via a symbol pointer.
-	| labelDynamic (thisPackage dflags) lbl 
-	= AccessViaSymbolPtr
-
- 	-- For PowerPC32 -fPIC, we have to access even static data
-	-- via a symbol pointer (see below for an explanation why
-	-- PowerPC32 Linux is especially broken).
-	| arch == ArchPPC
-	, opt_PIC
-	= AccessViaSymbolPtr
+howToAccessLabel dflags arch os DataReference lbl
+	| osElfTarget os
+	= case () of
+	    -- A dynamic label needs to be accessed via a symbol pointer.
+          _ | labelDynamic (thisPackage dflags) lbl 
+	    -> AccessViaSymbolPtr
+
+ 	    -- For PowerPC32 -fPIC, we have to access even static data
+	    -- via a symbol pointer (see below for an explanation why
+	    -- PowerPC32 Linux is especially broken).
+	    | arch == ArchPPC
+	    , opt_PIC
+	    -> AccessViaSymbolPtr
 	
-	| otherwise 
-	= AccessDirectly
+	    | otherwise 
+	    -> AccessDirectly
 
 
 	-- In most cases, we have to avoid symbol stubs on ELF, for the following reasons:
@@ -335,20 +336,21 @@
 	-- (AccessDirectly, because we get an implicit symbol stub)
 	-- and calling functions from PIC code on non-i386 platforms (via a symbol stub) 
 
-howToAccessLabel dflags arch OSLinux CallReference lbl
-	| labelDynamic (thisPackage dflags) lbl && not opt_PIC
+howToAccessLabel dflags arch os CallReference lbl
+	| osElfTarget os
+	, labelDynamic (thisPackage dflags) lbl && not opt_PIC
 	= AccessDirectly
 
-	| arch /= ArchX86
+	| osElfTarget os
+	, arch /= ArchX86
 	, labelDynamic (thisPackage dflags) lbl && opt_PIC
 	= AccessViaStub
 
-howToAccessLabel dflags _ OSLinux _ lbl
-	| labelDynamic (thisPackage dflags) lbl 
-	= AccessViaSymbolPtr
-
-	| otherwise 
-	= AccessDirectly
+howToAccessLabel dflags _ os _ lbl
+	| osElfTarget os
+	= if labelDynamic (thisPackage dflags) lbl 
+	    then AccessViaSymbolPtr
+	    else AccessDirectly
 
 -- all other platforms
 howToAccessLabel _ _ _ _ _
@@ -384,7 +386,8 @@
 -- We have made sure that *everything* is accessed indirectly, so this
 -- is only used for offsets from the GOT to symbol pointers inside the
 -- GOT.
-picRelative ArchPPC OSLinux lbl
+picRelative ArchPPC os lbl
+	| osElfTarget os
 	= CmmLabelDiffOff lbl gotLabel 0
 
 
@@ -396,7 +399,7 @@
 -- and a GotSymbolOffset label for other things.
 -- For reasons of tradition, the symbol offset label is written as a plain label.
 picRelative arch os lbl
-	| os == OSLinux || (os == OSDarwin && arch == ArchX86_64)
+	| osElfTarget os || (os == OSDarwin && arch == ArchX86_64)
 	= let	result
 			| Just (SymbolPtr, lbl') <- dynamicLinkerLabelInfo lbl
   			= CmmLabel $ mkDynamicLinkerLabel GotSymbolPtr lbl'
@@ -433,12 +436,12 @@
 	= True
 	
 	-- PowerPC Linux: -fPIC or -dynamic
-	| os	== OSLinux
+	| osElfTarget os
 	, arch	== ArchPPC
 	= opt_PIC || not opt_Static
 
 	-- i386 (and others?): -dynamic but not -fPIC
-	| os	== OSLinux
+	| osElfTarget os
 	, arch	/= ArchPPC_64
 	= not opt_Static && not opt_PIC
 
@@ -477,12 +480,14 @@
 -- The .LCTOC1 label is defined to point 32768 bytes into the table,
 -- to make the most of the PPC's 16-bit displacements.
 -- Only needed for PIC.
-pprGotDeclaration arch OSLinux
-	| arch	/= ArchPPC_64
+pprGotDeclaration arch os
+	| osElfTarget os
+	, arch	/= ArchPPC_64
 	, not opt_PIC 
 	= Pretty.empty
 
-	| arch	/= ArchPPC_64
+	| osElfTarget os
+	, arch	/= ArchPPC_64
 	= vcat [
 		ptext (sLit ".section \".got2\",\"aw\""),
 		ptext (sLit ".LCTOC1 = .+32768") ]
@@ -640,23 +645,26 @@
 -- the NCG will keep track of all DynamicLinkerLabels it uses
 -- and output each of them using pprImportedSymbol.
 
-pprImportedSymbol ArchPPC_64 OSLinux _
+pprImportedSymbol ArchPPC_64 os _
+	| osElfTarget os
 	= empty
 
-pprImportedSymbol _ OSLinux importedLbl
-	| Just (SymbolPtr, lbl)	<- dynamicLinkerLabelInfo importedLbl
-	= let	symbolSize = case wordWidth of
-		     W32 -> sLit "\t.long"
-		     W64 -> sLit "\t.quad"
-		     _ -> panic "Unknown wordRep in pprImportedSymbol"
-
-	  in vcat [
-	        ptext (sLit ".section \".got2\", \"aw\""),
-	        ptext (sLit ".LC_") <> pprCLabel_asm lbl <> char ':',
-	        ptext symbolSize <+> pprCLabel_asm lbl ]
+pprImportedSymbol _ os importedLbl
+	| osElfTarget os
+	= case dynamicLinkerLabelInfo importedLbl of
+	    Just (SymbolPtr, lbl)
+	      -> let symbolSize = case wordWidth of
+		         W32 -> sLit "\t.long"
+		         W64 -> sLit "\t.quad"
+		         _ -> panic "Unknown wordRep in pprImportedSymbol"
+
+	         in vcat [
+	              ptext (sLit ".section \".got2\", \"aw\""),
+	              ptext (sLit ".LC_") <> pprCLabel_asm lbl <> char ':',
+	              ptext symbolSize <+> pprCLabel_asm lbl ]
 
-	-- PLT code stubs are generated automatically by the dynamic linker.
-	| otherwise = empty
+	    -- PLT code stubs are generated automatically by the dynamic linker.
+	    _ -> empty
 
 pprImportedSymbol _ _ _
 	= panic "PIC.pprImportedSymbol: no match"
@@ -699,8 +707,9 @@
 	-> [NatCmmTop PPC.Instr] 
 	-> NatM [NatCmmTop PPC.Instr]
 
-initializePicBase_ppc ArchPPC OSLinux picReg
+initializePicBase_ppc ArchPPC os picReg
     (CmmProc info lab params (ListGraph blocks) : statics)
+    | osElfTarget os
     = do
         gotOffLabel <- getNewLabelNat
         tmp <- getNewRegNat $ intSize wordWidth
@@ -751,8 +760,9 @@
 	-> [NatCmmTop X86.Instr] 
 	-> NatM [NatCmmTop X86.Instr]
 
-initializePicBase_x86 ArchX86 OSLinux picReg 
+initializePicBase_x86 ArchX86 os picReg 
 	(CmmProc info lab params (ListGraph blocks) : statics)
+    | osElfTarget os
     = return (CmmProc info lab params (ListGraph (b':tail blocks)) : statics)
     where BasicBlock bID insns = head blocks
           b' = BasicBlock bID (X86.FETCHGOT picReg : insns)
diff -rN -u old-ghc/compiler/nativeGen/Platform.hs new-ghc/compiler/nativeGen/Platform.hs
--- old-ghc/compiler/nativeGen/Platform.hs	2010-01-03 23:07:52.000000000 +0100
+++ new-ghc/compiler/nativeGen/Platform.hs	2010-01-03 23:07:56.000000000 +0100
@@ -9,7 +9,8 @@
 	Arch(..),
 	OS(..),
 
-	defaultTargetPlatform
+	defaultTargetPlatform,
+	osElfTarget
 )
 
 where
@@ -47,9 +48,16 @@
 	| OSDarwin
 	| OSSolaris
 	| OSMinGW32
+	| OSFreeBSD
 	deriving (Show, Eq)
 
 
+-- | This predicates tells us whether the OS supports ELF-like shared libraries.
+osElfTarget :: OS -> Bool
+osElfTarget OSLinux   = True
+osElfTarget OSFreeBSD = True
+osElfTarget _         = False
+
 -- | This is the target platform as far as the #ifdefs are concerned.
 --	These are set in includes/ghcplatform.h by the autoconf scripts
 defaultTargetPlatform :: Platform
@@ -86,6 +94,8 @@
 defaultTargetOS	= OSSolaris
 #elif mingw32_TARGET_OS
 defaultTargetOS	= OSMinGW32
+#elif freebsd_TARGET_OS
+defaultTargetOS	= OSFreeBSD
 #else
 defaultTargetOS	= OSUnknown
 #endif
diff -rN -u old-ghc/libffi/ghc.mk new-ghc/libffi/ghc.mk
--- old-ghc/libffi/ghc.mk	2010-01-03 23:07:53.000000000 +0100
+++ new-ghc/libffi/ghc.mk	2010-01-03 23:08:00.000000000 +0100
@@ -88,8 +88,7 @@
 libffi_DYNAMIC_LIBS = libffi/libffi$(soext) libffi/libffi.5$(soext) libffi/libffi.5.0.9$(soext)
 else
 libffi_DYNAMIC_LIBS = libffi/dist-install/build/libffi.so \
-                      libffi/dist-install/build/libffi.so.5 \
-                      libffi/dist-install/build/libffi.so.5.0.9
+                      libffi/dist-install/build/libffi.so.5
 endif
 endif
 
diff -rN -u old-ghc/mk/config.mk.in new-ghc/mk/config.mk.in
--- old-ghc/mk/config.mk.in	2010-01-03 23:07:53.000000000 +0100
+++ new-ghc/mk/config.mk.in	2010-01-03 23:08:00.000000000 +0100
@@ -102,7 +102,7 @@
 GhcLibProfiled=$(if $(filter p,$(GhcLibWays)),YES,NO)
 
 # Do we support shared libs?
-PlatformSupportsSharedLibs = $(if $(filter $(TARGETPLATFORM),i386-unknown-linux x86_64-unknown-linux),YES,NO)
+PlatformSupportsSharedLibs = $(if $(filter $(TARGETPLATFORM),i386-unknown-linux x86_64-unknown-linux i386-unknown-freebsd amd64-unknown-freebsd),YES,NO)
 
 # ToDo later:
 # buildstaticli...@buildstaticlibs@
_______________________________________________
Cvs-ghc mailing list
Cvs-ghc@haskell.org
http://www.haskell.org/mailman/listinfo/cvs-ghc

Reply via email to