From 5fc4a6cbf12c9380a8e889173ba47888b3ebb511 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 12 May 2005 07:35:42 +0000 Subject: [PATCH 001/530] Setup of module ghc --- .cvsignore | 0 Makefile | 21 +++++++++++++++++++++ sources | 0 3 files changed, 21 insertions(+) create mode 100644 .cvsignore create mode 100644 Makefile create mode 100644 sources diff --git a/.cvsignore b/.cvsignore new file mode 100644 index 0000000..e69de29 diff --git a/Makefile b/Makefile new file mode 100644 index 0000000..d85df4e --- /dev/null +++ b/Makefile @@ -0,0 +1,21 @@ +# Makefile for source rpm: ghc +# $Id$ +NAME := ghc +SPECFILE = $(firstword $(wildcard *.spec)) + +define find-makefile-common +for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done +endef + +MAKEFILE_COMMON := $(shell $(find-makefile-common)) + +ifeq ($(MAKEFILE_COMMON),) +# attept a checkout +define checkout-makefile-common +test -f CVS/Root && { cvs -Q -d $$(cat CVS/Root) checkout common && echo "common/Makefile.common" ; } || { echo "ERROR: I can't figure out how to checkout the 'common' module." ; exit -1 ; } >&2 +endef + +MAKEFILE_COMMON := $(shell $(checkout-makefile-common)) +endif + +include $(MAKEFILE_COMMON) diff --git a/sources b/sources new file mode 100644 index 0000000..e69de29 From 01ca4204e687f486886b0fa193eefb9a43d0ee17 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 12 May 2005 07:37:43 +0000 Subject: [PATCH 002/530] auto-import ghc-6.4-8 on branch devel from ghc-6.4-8.src.rpm initial import to Extras --- .cvsignore | 1 + ghc-6.4-dsforeign-x86_64-1097471.patch | 249 +++++++++++++++++++ ghc-6.4-powerpc.patch | 26 ++ ghc-6.4-rts-adjustor-x86_64-1097471.patch | 250 +++++++++++++++++++ ghc.spec | 286 ++++++++++++++++++++++ rts-GCCompact.h-x86_64.patch | 32 +++ sources | 1 + 7 files changed, 845 insertions(+) create mode 100644 ghc-6.4-dsforeign-x86_64-1097471.patch create mode 100644 ghc-6.4-powerpc.patch create mode 100644 ghc-6.4-rts-adjustor-x86_64-1097471.patch create mode 100644 ghc.spec create mode 100644 rts-GCCompact.h-x86_64.patch diff --git a/.cvsignore b/.cvsignore index e69de29..9cbb0e0 100644 --- a/.cvsignore +++ b/.cvsignore @@ -0,0 +1 @@ +ghc-6.4-src.tar.bz2 diff --git a/ghc-6.4-dsforeign-x86_64-1097471.patch b/ghc-6.4-dsforeign-x86_64-1097471.patch new file mode 100644 index 0000000..3ecbb88 --- /dev/null +++ b/ghc-6.4-dsforeign-x86_64-1097471.patch @@ -0,0 +1,249 @@ +diff -u ghc-6.4/ghc/compiler/deSugar/DsForeign.lhs ghc-6.5/ghc/compiler/deSugar/DsForeign.lhs +--- ghc-6.4/ghc/compiler/deSugar/DsForeign.lhs 2005-05-07 11:51:04.000000000 +0900 ++++ ghc-6.5/ghc/compiler/deSugar/DsForeign.lhs 2005-05-07 11:51:04.000000000 +0900 +@@ -24,14 +24,14 @@ + import Type ( isUnLiftedType ) + #endif + import MachOp ( machRepByteWidth, MachRep(..) ) +-import SMRep ( argMachRep, primRepToCgRep ) ++import SMRep ( argMachRep, typeCgRep ) + import CoreUtils ( exprType, mkInlineMe ) + import Id ( Id, idType, idName, mkSysLocal, setInlinePragma ) + import Literal ( Literal(..), mkStringLit ) + import Module ( moduleString ) + import Name ( getOccString, NamedThing(..) ) + import OccName ( encodeFS ) +-import Type ( repType, coreEqType, typePrimRep ) ++import Type ( repType, coreEqType ) + import TcType ( Type, mkFunTys, mkForAllTys, mkTyConApp, + mkFunTy, tcSplitTyConApp_maybe, + tcSplitForAllTys, tcSplitFunTys, tcTyConAppArgs, +@@ -52,7 +52,7 @@ + import BasicTypes ( Activation( NeverActive ) ) + import SrcLoc ( Located(..), unLoc ) + import Outputable +-import Maybe ( fromJust ) ++import Maybe ( fromJust, isNothing ) + import FastString + \end{code} + +@@ -95,7 +95,7 @@ + combine (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) + (L loc (ForeignExport (L _ id) _ (CExport (CExportStatic ext_nm cconv)) depr)) + = dsFExport id (idType id) +- ext_nm cconv False `thenDs` \(h, c, _) -> ++ ext_nm cconv False `thenDs` \(h, c, _, _) -> + warnDepr depr loc `thenDs` \_ -> + returnDs (ForeignStubs (h $$ acc_h) (c $$ acc_c) acc_hdrs (id:acc_feb), + acc_f) +@@ -292,7 +292,8 @@ + -- the first argument's stable pointer + -> DsM ( SDoc -- contents of Module_stub.h + , SDoc -- contents of Module_stub.c +- , [Type] -- primitive arguments expected by stub function. ++ , [MachRep] -- primitive arguments expected by stub function ++ , Int -- size of args to stub function + ) + + dsFExport fn_id ty ext_name cconv isDyn +@@ -371,7 +372,8 @@ + in + dsLookupGlobalId bindIOName `thenDs` \ bindIOId -> + newSysLocalDs stable_ptr_ty `thenDs` \ stbl_value -> +- dsFExport id export_ty fe_nm cconv True `thenDs` \ (h_code, c_code, stub_args) -> ++ dsFExport id export_ty fe_nm cconv True ++ `thenDs` \ (h_code, c_code, arg_reps, args_size) -> + let + stbl_app cont ret_ty = mkApps (Var bindIOId) + [ Type stable_ptr_ty +@@ -395,9 +397,7 @@ + -- (probably in the RTS.) + adjustor = FSLIT("createAdjustor") + +- arg_type_info = drop 2 $ map (repCharCode.argMachRep +- .primRepToCgRep.typePrimRep) +- stub_args ++ arg_type_info = map repCharCode arg_reps + repCharCode F32 = 'f' + repCharCode F64 = 'd' + repCharCode I64 = 'l' +@@ -407,17 +407,9 @@ + -- so that we can attach the '@N' suffix to its label if it is a + -- stdcall on Windows. + mb_sz_args = case cconv of +- StdCallConv -> Just (sum (map ty_size stub_args)) ++ StdCallConv -> Just args_size + _ -> Nothing + +- -- NB. the calculation here isn't strictly speaking correct. +- -- We have a primitive Haskell type (eg. Int#, Double#), and +- -- we want to know the size, when passed on the C stack, of +- -- the associated C type (eg. HsInt, HsDouble). We don't have +- -- this information to hand, but we know what GHC's conventions +- -- are for passing around the primitive Haskell types, so we +- -- use that instead. I hope the two coincide --SDM +- ty_size = machRepByteWidth.argMachRep.primRepToCgRep.typePrimRep + in + dsCCall adjustor adj_args PlayRisky io_res_ty `thenDs` \ ccall_adj -> + -- PlayRisky: the adjustor doesn't allocate in the Haskell heap or do a callback +@@ -464,33 +456,33 @@ + -> CCallConv + -> (SDoc, + SDoc, +- [Type] -- the *primitive* argument types ++ [MachRep], -- the argument reps ++ Int -- total size of arguments + ) + mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc +- = (header_bits, c_bits, all_prim_arg_tys) ++ = (header_bits, c_bits, ++ [rep | (_,_,_,rep) <- arg_info], -- just the real args ++ sum [ machRepByteWidth rep | (_,_,_,rep) <- aug_arg_info] -- all the args ++ ) + where +- -- Create up types and names for the real args +- arg_cnames, arg_ctys :: [SDoc] +- arg_cnames = mkCArgNames 1 arg_htys +- arg_ctys = map showStgType arg_htys +- +- -- and also for auxiliary ones; the stable ptr in the dynamic case, and +- -- a slot for the dummy return address in the dynamic + ccall case +- extra_cnames_and_tys +- = case maybe_target of +- Nothing -> [((text "the_stableptr", text "StgStablePtr"), mkStablePtrPrimTy alphaTy)] +- other -> [] +- ++ +- case (maybe_target, cc) of +- (Nothing, CCallConv) -> [((text "original_return_addr", text "void*"), addrPrimTy)] +- other -> [] +- +- all_cnames_and_ctys :: [(SDoc, SDoc)] +- all_cnames_and_ctys +- = map fst extra_cnames_and_tys ++ zip arg_cnames arg_ctys +- +- all_prim_arg_tys +- = map snd extra_cnames_and_tys ++ map getPrimTyOf arg_htys ++ -- list the arguments to the C function ++ arg_info :: [(SDoc, -- arg name ++ SDoc, -- C type ++ Type, -- Haskell type ++ MachRep)] -- the MachRep ++ arg_info = [ (text ('a':show n), showStgType ty, ty, ++ typeMachRep (getPrimTyOf ty)) ++ | (ty,n) <- zip arg_htys [1..] ] ++ ++ -- add some auxiliary args; the stable ptr in the wrapper case, and ++ -- a slot for the dummy return address in the wrapper + ccall case ++ aug_arg_info ++ | isNothing maybe_target = stable_ptr_arg : insertRetAddr cc arg_info ++ | otherwise = arg_info ++ ++ stable_ptr_arg = ++ (text "the_stableptr", text "StgStablePtr", undefined, ++ typeMachRep (mkStablePtrPrimTy alphaTy)) + + -- stuff to do with the return type of the C function + res_hty_is_unit = res_hty `coreEqType` unitTy -- Look through any newtypes +@@ -506,8 +498,8 @@ + header_bits = ptext SLIT("extern") <+> fun_proto <> semi + + fun_proto = cResType <+> pprCconv <+> ftext c_nm <> +- parens (hsep (punctuate comma (map (\(nm,ty) -> ty <+> nm) +- all_cnames_and_ctys))) ++ parens (hsep (punctuate comma (map (\(nm,ty,_,_) -> ty <+> nm) ++ aug_arg_info))) + + -- the target which will form the root of what we ask rts_evalIO to run + the_cfun +@@ -517,9 +509,9 @@ + + -- the expression we give to rts_evalIO + expr_to_run +- = foldl appArg the_cfun (zip arg_cnames arg_htys) ++ = foldl appArg the_cfun arg_info -- NOT aug_arg_info + where +- appArg acc (arg_cname, arg_hty) ++ appArg acc (arg_cname, _, arg_hty, _) + = text "rts_apply" + <> parens (acc <> comma <> mkHObj arg_hty <> parens arg_cname) + +@@ -538,6 +530,30 @@ + Nothing -> empty + Just hs_fn -> text "extern StgClosure " <> ppr hs_fn <> text "_closure" <> semi + ++ -- the only reason for making the mingw32 (anything targetting PE, really) stick ++ -- out here is that the GHCi linker isn't capable of handling .ctors sections ++ useStaticConstructors ++#if defined(mingw32_HOST_OS) ++ = False ++#else ++ = True ++#endif ++ ++ initialiser ++ = case maybe_target of ++ Nothing -> empty ++ Just hs_fn ++ | not useStaticConstructors -> empty ++ | otherwise -> ++ vcat ++ [ text "static void stginit_export_" <> ppr hs_fn ++ <> text "() __attribute__((constructor));" ++ , text "static void stginit_export_" <> ppr hs_fn <> text "()" ++ , braces (text "getStablePtr" ++ <> parens (text "(StgPtr) &" <> ppr hs_fn <> text "_closure") ++ <> semi) ++ ] ++ + -- finally, the whole darn thing + c_bits = + space $$ +@@ -568,11 +584,17 @@ + , if res_hty_is_unit then empty + else text "return cret;" + , rbrace +- ] +- ++ ] $$ ++ initialiser + +-mkCArgNames :: Int -> [a] -> [SDoc] +-mkCArgNames n as = zipWith (\ _ n -> text ('a':show n)) as [n..] ++-- NB. the calculation here isn't strictly speaking correct. ++-- We have a primitive Haskell type (eg. Int#, Double#), and ++-- we want to know the size, when passed on the C stack, of ++-- the associated C type (eg. HsInt, HsDouble). We don't have ++-- this information to hand, but we know what GHC's conventions ++-- are for passing around the primitive Haskell types, so we ++-- use that instead. I hope the two coincide --SDM ++typeMachRep ty = argMachRep (typeCgRep ty) + + mkHObj :: Type -> SDoc + mkHObj t = text "rts_mk" <> text (showFFIType t) +@@ -590,6 +612,26 @@ + Just (tc,_) -> tc + Nothing -> pprPanic "showFFIType" (ppr t) + ++#if !defined(x86_64_TARGET_ARCH) ++insertRetAddr CCallConv args = ret_addr_arg : args ++insertRetAddr _ args = args ++#else ++-- On x86_64 we insert the return address after the 6th ++-- integer argument, because this is the point at which we ++-- need to flush a register argument to the stack (See rts/Adjustor.c for ++-- details). ++insertRetAddr CCallConv args = go 0 args ++ where go 6 args = ret_addr_arg : args ++ go n (arg@(_,_,_,rep):args) ++ | I64 <- rep = arg : go (n+1) args ++ | otherwise = arg : go n args ++ go n [] = [] ++insertRetAddr _ args = args ++#endif ++ ++ret_addr_arg = (text "original_return_addr", text "void*", undefined, ++ typeMachRep addrPrimTy) ++ + -- This function returns the primitive type associated with the boxed + -- type argument to a foreign export (eg. Int ==> Int#). It assumes + -- that all the types we are interested in have a single constructor diff --git a/ghc-6.4-powerpc.patch b/ghc-6.4-powerpc.patch new file mode 100644 index 0000000..7fc7ccd --- /dev/null +++ b/ghc-6.4-powerpc.patch @@ -0,0 +1,26 @@ +diff -ur ghc-6.4/distrib/configure-bin.ac ghc-6.4/distrib/configure-bin.ac +--- ghc-6.4/distrib/configure-bin.ac 2005-03-10 09:10:09.000000000 -0500 ++++ ghc-6.4/distrib/configure-bin.ac 2005-03-14 21:37:20.356380744 -0500 +@@ -78,6 +78,10 @@ + TargetPlatform=rs6000-ibm-aix;; + powerpc-apple-darwin*) + TargetPlatform=powerpc-apple-darwin;; ++powerpc-*-linux*) ++ TargetPlatform=powerpc-unknown-linux;; ++powerpc64-*-linux*) ++ TargetPlatform=powerpc64-unknown-linux;; + sparc-sun-sunos4*) + TargetPlatform=sparc-sun-sunos4;; + sparc-sun-solaris2*) +diff -ur ghc-6.4/ghc/includes/MachRegs.h ghc-6.4/ghc/includes/MachRegs.h +--- ghc-6.4/ghc/includes/MachRegs.h 2005-01-28 07:55:51.000000000 -0500 ++++ ghc-6.4/ghc/includes/MachRegs.h 2005-03-14 21:37:31.825368128 -0500 +@@ -457,7 +457,7 @@ + #define REG_R7 r20 + #define REG_R8 r21 + +-#ifdef darwin_REGS ++#if darwin_REGS + + #define REG_F1 f14 + #define REG_F2 f15 diff --git a/ghc-6.4-rts-adjustor-x86_64-1097471.patch b/ghc-6.4-rts-adjustor-x86_64-1097471.patch new file mode 100644 index 0000000..c77260d --- /dev/null +++ b/ghc-6.4-rts-adjustor-x86_64-1097471.patch @@ -0,0 +1,250 @@ +diff -u ghc-6.4/ghc/rts/Adjustor.c ghc-6.5/ghc/rts/Adjustor.c +--- ghc-6.4/ghc/rts/Adjustor.c 2005-05-07 11:46:10.000000000 +0900 ++++ ghc-6.5/ghc/rts/Adjustor.c 2005-05-07 11:46:11.000000000 +0900 +@@ -46,13 +46,18 @@ + #include + #endif + +-#if defined(openbsd_HOST_OS) ++#if defined(openbsd_HOST_OS) || defined(linux_HOST_OS) + #include + #include + #include + + /* no C99 header stdint.h on OpenBSD? */ ++#if defined(openbsd_HOST_OS) + typedef unsigned long my_uintptr_t; ++#else ++#include ++typedef uintptr_t my_uintptr_t; ++#endif + #endif + + #if defined(powerpc_HOST_ARCH) && defined(linux_HOST_OS) +@@ -80,7 +85,7 @@ + barf("mallocBytesRWX: failed to protect 0x%p; error=%lu; old protection: %lu\n", + addr, (unsigned long)GetLastError(), (unsigned long)dwOldProtect); + } +-#elif defined(openbsd_HOST_OS) ++#elif defined(openbsd_HOST_OS) || defined(linux_HOST_OS) + /* malloced memory isn't executable by default on OpenBSD */ + my_uintptr_t pageSize = sysconf(_SC_PAGESIZE); + my_uintptr_t mask = ~(pageSize - 1); +@@ -94,8 +99,46 @@ + return addr; + } + ++#ifdef LEADING_UNDERSCORE ++#define UNDERSCORE "_" ++#else ++#define UNDERSCORE "" ++#endif + #if defined(i386_HOST_ARCH) +-static unsigned char *obscure_ccall_ret_code; ++/* ++ Now here's something obscure for you: ++ ++ When generating an adjustor thunk that uses the C calling ++ convention, we have to make sure that the thunk kicks off ++ the process of jumping into Haskell with a tail jump. Why? ++ Because as a result of jumping in into Haskell we may end ++ up freeing the very adjustor thunk we came from using ++ freeHaskellFunctionPtr(). Hence, we better not return to ++ the adjustor code on our way out, since it could by then ++ point to junk. ++ ++ The fix is readily at hand, just include the opcodes ++ for the C stack fixup code that we need to perform when ++ returning in some static piece of memory and arrange ++ to return to it before tail jumping from the adjustor thunk. ++*/ ++__asm__ ( ++ ".globl " UNDERSCORE "obscure_ccall_ret_code\n" ++ UNDERSCORE "obscure_ccall_ret_code:\n\t" ++ "addl $0x4, %esp\n\t" ++ "ret" ++ ); ++extern void obscure_ccall_ret_code(void); ++#endif ++ ++#if defined(x86_64_HOST_ARCH) ++__asm__ ( ++ ".globl " UNDERSCORE "obscure_ccall_ret_code\n" ++ UNDERSCORE "obscure_ccall_ret_code:\n\t" ++ "addq $0x8, %rsp\n\t" ++ "ret" ++ ); ++extern void obscure_ccall_ret_code(void); + #endif + + #if defined(alpha_HOST_ARCH) +@@ -195,7 +238,7 @@ + createAdjustor(int cconv, StgStablePtr hptr, + StgFunPtr wptr, + char *typeString +-#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) ++#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) && !defined(x86_64_HOST_ARCH) + STG_UNUSED + #endif + ) +@@ -279,6 +322,111 @@ + adj_code[0x0f] = (unsigned char)0xff; /* jmp *%eax */ + adj_code[0x10] = (unsigned char)0xe0; + } ++#elif defined(x86_64_HOST_ARCH) ++ /* ++ stack at call: ++ argn ++ ... ++ arg7 ++ return address ++ %rdi,%rsi,%rdx,%rcx,%r8,%r9 = arg0..arg6 ++ ++ if there are <6 integer args, then we can just push the ++ StablePtr into %edi and shuffle the other args up. ++ ++ If there are >=6 integer args, then we have to flush one arg ++ to the stack, and arrange to adjust the stack ptr on return. ++ The stack will be rearranged to this: ++ ++ argn ++ ... ++ arg7 ++ return address *** <-- dummy arg in stub fn. ++ arg6 ++ obscure_ccall_ret_code ++ ++ This unfortunately means that the type of the stub function ++ must have a dummy argument for the original return address ++ pointer inserted just after the 6th integer argument. ++ ++ Code for the simple case: ++ ++ 0: 4d 89 c1 mov %r8,%r9 ++ 3: 49 89 c8 mov %rcx,%r8 ++ 6: 48 89 d1 mov %rdx,%rcx ++ 9: 48 89 f2 mov %rsi,%rdx ++ c: 48 89 fe mov %rdi,%rsi ++ f: 48 8b 3d 0a 00 00 00 mov 10(%rip),%rdi ++ 16: e9 00 00 00 00 jmpq stub_function ++ ... ++ 20: .quad 0 # aligned on 8-byte boundary ++ ++ ++ And the version for >=6 integer arguments: ++ ++ 0: 41 51 push %r9 ++ 2: 68 00 00 00 00 pushq $obscure_ccall_ret_code ++ 7: 4d 89 c1 mov %r8,%r9 ++ a: 49 89 c8 mov %rcx,%r8 ++ d: 48 89 d1 mov %rdx,%rcx ++ 10: 48 89 f2 mov %rsi,%rdx ++ 13: 48 89 fe mov %rdi,%rsi ++ 16: 48 8b 3d 0b 00 00 00 mov 11(%rip),%rdi ++ 1d: e9 00 00 00 00 jmpq stub_function ++ ... ++ 28: .quad 0 # aligned on 8-byte boundary ++ */ ++ ++ /* we assume the small code model (gcc -mcmmodel=small) where ++ * all symbols are <2^32, so hence wptr should fit into 32 bits. ++ */ ++ ASSERT(((long)wptr >> 32) == 0); ++ ++ { ++ int i = 0; ++ char *c; ++ ++ // determine whether we have 6 or more integer arguments, ++ // and therefore need to flush one to the stack. ++ for (c = typeString; *c != '\0'; c++) { ++ if (*c == 'i' || *c == 'l') i++; ++ if (i == 6) break; ++ } ++ ++ if (i < 6) { ++ adjustor = mallocBytesRWX(40); ++ ++ *(StgInt32 *)adjustor = 0x49c1894d; ++ *(StgInt32 *)(adjustor+4) = 0x8948c889; ++ *(StgInt32 *)(adjustor+8) = 0xf28948d1; ++ *(StgInt32 *)(adjustor+12) = 0x48fe8948; ++ *(StgInt32 *)(adjustor+16) = 0x000a3d8b; ++ *(StgInt32 *)(adjustor+20) = 0x00e90000; ++ ++ *(StgInt32 *)(adjustor+23) = ++ (StgInt32)((StgInt64)wptr - (StgInt64)adjustor - 27); ++ *(StgInt64 *)(adjustor+32) = (StgInt64)hptr; ++ } ++ else ++ { ++ adjustor = mallocBytesRWX(48); ++ ++ *(StgInt32 *)adjustor = 0x00685141; ++ *(StgInt32 *)(adjustor+4) = 0x4d000000; ++ *(StgInt32 *)(adjustor+8) = 0x8949c189; ++ *(StgInt32 *)(adjustor+12) = 0xd18948c8; ++ *(StgInt32 *)(adjustor+16) = 0x48f28948; ++ *(StgInt32 *)(adjustor+20) = 0x8b48fe89; ++ *(StgInt32 *)(adjustor+24) = 0x00000b3d; ++ *(StgInt32 *)(adjustor+28) = 0x0000e900; ++ ++ *(StgInt32 *)(adjustor+3) = ++ (StgInt32)(StgInt64)obscure_ccall_ret_code; ++ *(StgInt32 *)(adjustor+30) = ++ (StgInt32)((StgInt64)wptr - (StgInt64)adjustor - 34); ++ *(StgInt64 *)(adjustor+40) = (StgInt64)hptr; ++ } ++ } + #elif defined(sparc_HOST_ARCH) + /* Magic constant computed by inspecting the code length of the following + assembly language snippet (offset and machine code prefixed): +@@ -848,7 +996,16 @@ + freeStablePtr(*((StgStablePtr*)((unsigned char*)ptr + 0x01))); + } else { + freeStablePtr(*((StgStablePtr*)((unsigned char*)ptr + 0x02))); +- } ++ } ++#elif defined(x86_64_HOST_ARCH) ++ if ( *(StgWord16 *)ptr == 0x894d ) { ++ freeStablePtr(*(StgStablePtr*)(ptr+32)); ++ } else if ( *(StgWord16 *)ptr == 0x5141 ) { ++ freeStablePtr(*(StgStablePtr*)(ptr+40)); ++ } else { ++ errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); ++ return; ++ } + #elif defined(sparc_HOST_ARCH) + if ( *(unsigned long*)ptr != 0x9C23A008UL ) { + errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); +@@ -906,30 +1063,4 @@ + void + initAdjustor(void) + { +-#if defined(i386_HOST_ARCH) +- /* Now here's something obscure for you: +- +- When generating an adjustor thunk that uses the C calling +- convention, we have to make sure that the thunk kicks off +- the process of jumping into Haskell with a tail jump. Why? +- Because as a result of jumping in into Haskell we may end +- up freeing the very adjustor thunk we came from using +- freeHaskellFunctionPtr(). Hence, we better not return to +- the adjustor code on our way out, since it could by then +- point to junk. +- +- The fix is readily at hand, just include the opcodes +- for the C stack fixup code that we need to perform when +- returning in some static piece of memory and arrange +- to return to it before tail jumping from the adjustor thunk. +- */ +- +- obscure_ccall_ret_code = mallocBytesRWX(4); +- +- obscure_ccall_ret_code[0x00] = (unsigned char)0x83; /* addl $0x4, %esp */ +- obscure_ccall_ret_code[0x01] = (unsigned char)0xc4; +- obscure_ccall_ret_code[0x02] = (unsigned char)0x04; +- +- obscure_ccall_ret_code[0x03] = (unsigned char)0xc3; /* ret */ +-#endif + } diff --git a/ghc.spec b/ghc.spec new file mode 100644 index 0000000..fad900d --- /dev/null +++ b/ghc.spec @@ -0,0 +1,286 @@ +%define build_version 6.4 +%define ghcver ghc64 + +# speed up test builds by not building profiled libraries +%define build_prof 1 +%define build_doc 0 + +# ghc-6.4 doesn't build with gcc-4.0 yet +%define _with_gcc32 %{nil} + +Name: ghc +Version: 6.4 +Release: 8 +Summary: Glasgow Haskell Compilation system +License: BSD style +Group: Development/Languages +Source: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +URL: http://haskell.org/ghc/ +Requires: %{ghcver} = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +BuildRequires: sed, %{ghcver}, %{?_with_gcc32: compat-gcc-32} +Buildrequires: gmp-devel, readline-devel, xorg-x11-devel, freeglut-devel, openal-devel +%if %{build_doc} +# haddock generates libraries/ docs +Buildrequires: libxslt, docbook-style-xsl, haddock +%endif +Prefix: %{_prefix} +Patch1: ghc-6.4-powerpc.patch +Patch2: rts-GCCompact.h-x86_64.patch +Patch3: ghc-6.4-dsforeign-x86_64-1097471.patch +Patch4: ghc-6.4-rts-adjustor-x86_64-1097471.patch + +%description +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interface. + +%package -n %{ghcver} +Summary: Documentation for GHC +Group: Development/Languages +Requires: gcc gmp-devel readline-devel + +%description -n %{ghcver} +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interfaces. + +This package contains all the main files and libraries of version %{version}. + +%if %{build_prof} +%package -n %{ghcver}-prof +Summary: Profiling libraries for GHC +Group: Development/Libraries +Requires: %{ghcver} = %{version}-%{release} +Obsoletes: ghc-prof + +%description -n %{ghcver}-prof +Profiling libraries for Glorious Glasgow Haskell Compilation System +(GHC). They should be installed when GHC's profiling subsystem is +needed. +%endif + +%package doc +Summary: Documentation for GHC +Group: Development/Languages + +%description doc +Preformatted documentation for the Glorious Glasgow Haskell +Compilation System (GHC) and its libraries. It should be installed if +you like to have local access to the documentation in HTML format. + +# the debuginfo subpackage is currently empty anyway, so don't generate it +%define debug_package %{nil} +%define __spec_install_post /usr/lib/rpm/brp-compress + +%prep +%setup -q -n ghc-%{version} +%patch1 -p1 -b .1-ppc +%patch2 -p1 -b .2-x86_64 +%patch3 -p1 -b .3-x86_64 +%patch4 -p1 -b .4-x86_64 + +%build +%ifarch x86_64 +echo "SplitObjs = NO" >> mk/build.mk +echo "GhcWithInterpreter = NO" >> mk/build.mk +%endif +%if !%{build_prof} +echo "GhcLibWays=" >> mk/build.mk +echo "GhcRTSWays=thr debug" >> mk/build.mk +%endif + +./configure --prefix=%{_prefix} --libdir=%{_libdir} --with-ghc=ghc-%{build_version} %{?_with_gcc32: --with-gcc=%{_bindir}/gcc32} + +make all +%if %{build_doc} +make html +%endif + +%install +rm -rf $RPM_BUILD_ROOT + +make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} install + +%if %{build_doc} +make datadir=$RPM_BUILD_ROOT%{_docdir}/ghc-%{version} XMLDocWays="html" install-docs +%endif + +SRC_TOP=$PWD +rm -f rpm-*-filelist rpm-*.files +( cd $RPM_BUILD_ROOT + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) +) + +# make paths absolute (filter "./usr" to "/usr") +sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files + +cat rpm-dir.files rpm-lib.files > rpm-base-filelist +%if %{build_prof} +cat rpm-dir.files rpm-prof.files > rpm-prof-filelist +%endif + +%clean +rm -rf $RPM_BUILD_ROOT + +%post +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} +fi + +%post -n %{ghcver} +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf +fi + +%files +%defattr(-,root,root,-) +%{_bindir}/* +%exclude %{_bindir}/ghc*%{version} + +%files -n %{ghcver} -f rpm-base-filelist +%defattr(-,root,root,-) +%doc ghc/ANNOUNCE ghc/LICENSE ghc/README +%{_bindir}/ghc*%{version} +%config(noreplace) %{_libdir}/ghc-%{version}/package.conf + +%if %{build_prof} +%files -n %{ghcver}-prof -f rpm-prof-filelist +%defattr(-,root,root,-) +%endif + +%if %{build_doc} +%files doc +%defattr(-,root,root,-) +%{_docdir}/%{name}-%{version} +%endif + +%changelog +* Thu May 12 2005 Jens Petersen - 6.4-8 +- initial import into Fedora Extras + +* Thu May 12 2005 Jens Petersen +- add build_prof and build_doc switches for -doc and -prof subpackages +- add _with_gcc32 switch since ghc-6.4 doesn't build with gcc-4.0 + +* Wed May 11 2005 Jens Petersen - 6.4-7 +- make package relocatable (ghc#1084122) + - add post install scripts to replace prefix in driver scripts +- buildrequire libxslt and docbook-style-xsl instead of docbook-utils and flex + +* Fri May 6 2005 Jens Petersen - 6.4-6 +- add ghc-6.4-dsforeign-x86_64-1097471.patch and + ghc-6.4-rts-adjustor-x86_64-1097471.patch from trunk to hopefully fix + ffi support on x86_64 (Simon Marlow, ghc#1097471) +- use XMLDocWays instead of SGMLDocWays to build documentation fully + +* Mon May 2 2005 Jens Petersen - 6.4-5 +- add rts-GCCompact.h-x86_64.patch to fix GC issue on x86_64 (Simon Marlow) + +* Thu Mar 17 2005 Jens Petersen - 6.4-4 +- add ghc-6.4-powerpc.patch (Ryan Lortie) +- disable building interpreter rather than install and delete on x86_64 + +* Wed Mar 16 2005 Jens Petersen - 6.4-3 +- make ghc require ghcver of same ver-rel +- on x86_64 remove ghci for now since it doesn't work and all .o files + +* Tue Mar 15 2005 Jens Petersen - 6.4-2 +- ghc requires ghcver (Amanda Clare) + +* Sat Mar 12 2005 Jens Petersen - 6.4-1 +- 6.4 release + - x86_64 build no longer unregisterised +- use sed instead of perl to tidy filelists +- buildrequire ghc64 instead of ghc-6.4 +- no epoch for ghc64-prof's ghc64 requirement +- install docs directly in docdir + +* Fri Jan 21 2005 Jens Petersen - 6.2.2-2 +- add x86_64 port + - build unregistered and without splitobjs + - specify libdir to configure and install +- rename ghc-prof to ghcXYZ-prof, which obsoletes ghc-prof + +* Mon Dec 6 2004 Jens Petersen - 6.2.2-1 +- move ghc requires to ghcXYZ + +* Wed Nov 24 2004 Jens Petersen - 6.2.2-0.fdr.1 +- ghc622 + - provide ghc = %%version +- require gcc, gmp-devel and readline-devel + +* Fri Oct 15 2004 Gerard Milmeister - 6.2.2-0.fdr.1 +- New Version 6.2.2 + +* Mon Mar 22 2004 Gerard Milmeister - 6.2.1-0.fdr.1 +- New Version 6.2.1 + +* Tue Dec 16 2003 Gerard Milmeister - 6.2-0.fdr.1 +- New Version 6.2 + +* Tue Dec 16 2003 Gerard Milmeister - 6.0.1-0.fdr.3 +- A few minor specfile tweaks + +* Mon Dec 15 2003 Gerard Milmeister - 6.0.1-0.fdr.2 +- Different file list generation + +* Mon Oct 20 2003 Gerard Milmeister - 6.0.1-0.fdr.1 +- First Fedora release +- Added generated html docs, so that haddock is not needed + +* Wed Sep 26 2001 Manuel Chakravarty +- small changes for 5.04 + +* Wed Sep 26 2001 Manuel Chakravarty +- split documentation off into a separate package +- adapt to new docbook setup in RH7.1 + +* Mon Apr 16 2001 Manuel Chakravarty +- revised for 5.00 +- also runs autoconf automagically if no ./configure found + +* Thu Jun 22 2000 Sven Panne +- removed explicit usage of hslibs/docs, it belongs to ghc/docs/set + +* Sun Apr 23 2000 Manuel Chakravarty +- revised for ghc 4.07; added suggestions from Pixel +- added profiling package + +* Tue Dec 7 1999 Manuel Chakravarty +- version for use from CVS + +* Thu Sep 16 1999 Manuel Chakravarty +- modified for GHC 4.04, patchlevel 1 (no more 62 tuple stuff); minimises use + of patch files - instead emits a build.mk on-the-fly + +* Sat Jul 31 1999 Manuel Chakravarty +- modified for GHC 4.04 + +* Wed Jun 30 1999 Manuel Chakravarty +- some more improvements from vbzoli + +* Fri Feb 26 1999 Manuel Chakravarty +- modified for GHC 4.02 + +* Thu Dec 24 1998 Zoltan Vorosbaranyi +- added BuildRoot +- files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib + +* Tue Jul 28 1998 Manuel Chakravarty +- original version diff --git a/rts-GCCompact.h-x86_64.patch b/rts-GCCompact.h-x86_64.patch new file mode 100644 index 0000000..b640508 --- /dev/null +++ b/rts-GCCompact.h-x86_64.patch @@ -0,0 +1,32 @@ +--- fptools/ghc/rts/GCCompact.h 2004/09/12 11:27:14 1.4 ++++ fptools/ghc/rts/GCCompact.h 2005/04/29 16:18:58 1.5 +@@ -12,7 +12,7 @@ mark(StgPtr p, bdescr *bd) + nat offset_within_block = p - bd->start; // in words + StgPtr bitmap_word = (StgPtr)bd->u.bitmap + + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); +- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); ++ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + *bitmap_word |= bit_mask; + } + +@@ -22,17 +22,17 @@ unmark(StgPtr p, bdescr *bd) + nat offset_within_block = p - bd->start; // in words + StgPtr bitmap_word = (StgPtr)bd->u.bitmap + + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); +- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); ++ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + *bitmap_word &= ~bit_mask; + } + +-INLINE_HEADER int ++INLINE_HEADER StgWord + is_marked(StgPtr p, bdescr *bd) + { + nat offset_within_block = p - bd->start; // in words + StgPtr bitmap_word = (StgPtr)bd->u.bitmap + + (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); +- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); ++ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); + return (*bitmap_word & bit_mask); + } + diff --git a/sources b/sources index e69de29..39fe85b 100644 --- a/sources +++ b/sources @@ -0,0 +1 @@ +45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 From 87abc3c55c784dd41ace37e7a783f02a4820eeb3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 12 May 2005 08:00:41 +0000 Subject: [PATCH 003/530] deliberately break building for now since ghc doesn't build yet with gcc4 (Warren Togami) --- ghc.spec | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/ghc.spec b/ghc.spec index fad900d..690071d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,3 +1,7 @@ +# FIXME - break-build placeholder for devel +# if you really want to build from this then comment out the following: +echo "** ghc currently requires gcc32 to build in fc4! **" && exit 1 + %define build_version 6.4 %define ghcver ghc64 From 0581bc18836b41a4f016631f5b9609949d4e1438 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 12 May 2005 09:22:03 +0000 Subject: [PATCH 004/530] break build (since BRs compat-gcc) in a more Makefile.common friendly way --- ghc.spec | 8 +++----- 1 file changed, 3 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 690071d..1a38605 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,7 +1,3 @@ -# FIXME - break-build placeholder for devel -# if you really want to build from this then comment out the following: -echo "** ghc currently requires gcc32 to build in fc4! **" && exit 1 - %define build_version 6.4 %define ghcver ghc64 @@ -88,7 +84,9 @@ you like to have local access to the documentation in HTML format. %define __spec_install_post /usr/lib/rpm/brp-compress %prep -%setup -q -n ghc-%{version} +## FIXME: ghc currently doesn't build with gcc4 +## to do a test build uncomment %%setup +#%%setup -q -n ghc-%{version} %patch1 -p1 -b .1-ppc %patch2 -p1 -b .2-x86_64 %patch3 -p1 -b .3-x86_64 From 2a0c7d6865175b0558c8bcbe2fbd470ee309455c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 19 May 2005 10:33:43 +0000 Subject: [PATCH 005/530] restore %setup so that it builds again --- ghc.spec | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 1a38605..fad900d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -84,9 +84,7 @@ you like to have local access to the documentation in HTML format. %define __spec_install_post /usr/lib/rpm/brp-compress %prep -## FIXME: ghc currently doesn't build with gcc4 -## to do a test build uncomment %%setup -#%%setup -q -n ghc-%{version} +%setup -q -n ghc-%{version} %patch1 -p1 -b .1-ppc %patch2 -p1 -b .2-x86_64 %patch3 -p1 -b .3-x86_64 From a677d5cbbfecfa1f756b791957e651853d5427d1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 31 May 2005 11:04:47 +0000 Subject: [PATCH 006/530] - add bootstrap files for i386, ppc and x86_64 - add temporary bootstrap spec file - temporarily point Makefile at ghc-bootstrap.spec - add ghc-doc-no-ps-install.patch to avoid install of ps docs --- .cvsignore | 3 + Makefile | 4 +- ghc-bootstrap.spec | 231 ++++++++++++++++++++++++++++++++++++ ghc-doc-no-ps-install.patch | 12 ++ ghc.spec | 5 +- sources | 3 + 6 files changed, 256 insertions(+), 2 deletions(-) create mode 100644 ghc-bootstrap.spec create mode 100644 ghc-doc-no-ps-install.patch diff --git a/.cvsignore b/.cvsignore index 9cbb0e0..cad5ac1 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1,4 @@ ghc-6.4-src.tar.bz2 +ghc-6.4-i386-unknown-linux.tar.bz2 +ghc-6.4-x86_64-unknown-linux.tar.bz2 +ghc-6.4-ppc-unknown-linux.tar.bz2 diff --git a/Makefile b/Makefile index d85df4e..d6abb41 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,9 @@ # Makefile for source rpm: ghc # $Id$ NAME := ghc -SPECFILE = $(firstword $(wildcard *.spec)) +#SPECFILE = $(firstword $(wildcard *.spec)) +# for bootstrap +SPECFILE = ghc-bootstrap.spec define find-makefile-common for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done diff --git a/ghc-bootstrap.spec b/ghc-bootstrap.spec new file mode 100644 index 0000000..a5d6f1c --- /dev/null +++ b/ghc-bootstrap.spec @@ -0,0 +1,231 @@ +## ghc seeding bootstrap spec file + +%define ghcver ghc64 + +Name: ghc +Version: 6.4 +Release: 1%{?dist} +Summary: Glasgow Haskell Compilation system +License: BSD style +Group: Development/Languages +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-i386-unknown-linux.tar.bz2 +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-ppc-unknown-linux.tar.bz2 +Source3: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-x86_64-unknown-linux.tar.bz2 +URL: http://haskell.org/ghc/ +Requires: %{ghcver} = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +BuildRequires: sed +Prefix: %{_prefix} +Patch1: ghc-doc-no-ps-install.patch +ExclusiveArch: i386 ppc x86_64 + +%description +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interface. + +%package -n %{ghcver} +Summary: Documentation for GHC +Group: Development/Languages +Requires: gcc gmp-devel readline-devel + +%description -n %{ghcver} +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interfaces. + +This package contains all the main files and libraries of version %{version}. + +%package -n %{ghcver}-prof +Summary: Profiling libraries for GHC +Group: Development/Libraries +Requires: %{ghcver} = %{version}-%{release} +Obsoletes: ghc-prof + +%description -n %{ghcver}-prof +Profiling libraries for Glorious Glasgow Haskell Compilation System +(GHC). They should be installed when GHC's profiling subsystem is +needed. + +%package doc +Summary: Documentation for GHC +Group: Development/Languages + +%description doc +Preformatted documentation for the Glorious Glasgow Haskell +Compilation System (GHC) and its libraries. It should be installed if +you like to have local access to the documentation in HTML format. + +# the debuginfo subpackage is currently empty anyway, so don't generate it +%define debug_package %{nil} +%define __spec_install_post /usr/lib/rpm/brp-compress + +%prep +rm -rf %{name}-%{version} +tar jxf ${RPM_SOURCE_DIR}/%{name}-%{version}-%{_arch}-unknown-linux.tar.bz2 +%setup -T -D +%patch1 -p1 -b .ps + +%build +./configure --prefix=%{_prefix} --libdir=%{_libdir} +make prefix=%{_prefix} libdir=%{_libdir}/%{name}-%{version} + +%install +rm -rf $RPM_BUILD_ROOT + +make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} datadir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} htmldir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} install-dirs install-bin install-libs install-datas install-docs + +SRC_TOP=$PWD +rm -f rpm-*-filelist rpm-*.files +( cd $RPM_BUILD_ROOT + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) +) + +# make paths absolute (filter "./usr" to "/usr") +sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files + +cat rpm-dir.files rpm-lib.files > rpm-base-filelist +cat rpm-dir.files rpm-prof.files > rpm-prof-filelist + +%clean +rm -rf $RPM_BUILD_ROOT + +%post +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} +fi + +%post -n %{ghcver} +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf +fi + +%files +%defattr(-,root,root,-) +%{_bindir}/* +%exclude %{_bindir}/ghc*%{version} + +%files -n %{ghcver} -f rpm-base-filelist +%defattr(-,root,root,-) +%doc ANNOUNCE LICENSE README +%{_bindir}/ghc*%{version} +%config(noreplace) %{_libdir}/ghc-%{version}/package.conf + +%files -n %{ghcver}-prof -f rpm-prof-filelist +%defattr(-,root,root,-) + +%files doc +%defattr(-,root,root,-) +%{_docdir}/%{name}-%{version} + +%changelog +* Tue May 31 2005 Jens Petersen +- initial seed bootstrap package for Fedora Extras for i386, ppc and x86_64 +- add %%dist to release + +* Thu May 12 2005 Jens Petersen +- add build_prof and build_doc switches for -doc and -prof subpackages + +* Wed May 11 2005 Jens Petersen +- make package relocatable (ghc#1084122) + - add post install scripts to replace prefix in driver scripts + +* Wed Mar 16 2005 Jens Petersen +- make ghc require ghcver of same ver-rel + +* Tue Mar 15 2005 Jens Petersen +- ghc requires ghcver (Amanda Clare) + +* Sat Mar 12 2005 Jens Petersen +- 6.4 release +- use sed instead of perl to tidy filelists +- no epoch for ghc64-prof's ghc64 requirement + +* Fri Jan 21 2005 Jens Petersen - 6.2.2-2 +- add x86_64 port + - build unregistered and without splitobjs + - specify libdir to configure and install +- rename ghc-prof to ghcXYZ-prof, which obsoletes ghc-prof + +* Mon Dec 6 2004 Jens Petersen - 6.2.2-1 +- move ghc requires to ghcXYZ + +* Wed Nov 24 2004 Jens Petersen - 6.2.2-0.fdr.1 +- ghc622 + - provide ghc = %%version +- require gcc, gmp-devel and readline-devel + +* Fri Oct 15 2004 Gerard Milmeister - 6.2.2-0.fdr.1 +- New Version 6.2.2 + +* Mon Mar 22 2004 Gerard Milmeister - 6.2.1-0.fdr.1 +- New Version 6.2.1 + +* Tue Dec 16 2003 Gerard Milmeister - 6.2-0.fdr.1 +- New Version 6.2 + +* Tue Dec 16 2003 Gerard Milmeister - 6.0.1-0.fdr.3 +- A few minor specfile tweaks + +* Mon Dec 15 2003 Gerard Milmeister - 6.0.1-0.fdr.2 +- Different file list generation + +* Mon Oct 20 2003 Gerard Milmeister - 6.0.1-0.fdr.1 +- First Fedora release +- Added generated html docs, so that haddock is not needed + +* Wed Sep 26 2001 Manuel Chakravarty +- small changes for 5.04 + +* Wed Sep 26 2001 Manuel Chakravarty +- split documentation off into a separate package +- adapt to new docbook setup in RH7.1 + +* Mon Apr 16 2001 Manuel Chakravarty +- revised for 5.00 +- also runs autoconf automagically if no ./configure found + +* Thu Jun 22 2000 Sven Panne +- removed explicit usage of hslibs/docs, it belongs to ghc/docs/set + +* Sun Apr 23 2000 Manuel Chakravarty +- revised for ghc 4.07; added suggestions from Pixel +- added profiling package + +* Tue Dec 7 1999 Manuel Chakravarty +- version for use from CVS + +* Thu Sep 16 1999 Manuel Chakravarty +- modified for GHC 4.04, patchlevel 1 (no more 62 tuple stuff); minimises use + of patch files - instead emits a build.mk on-the-fly + +* Sat Jul 31 1999 Manuel Chakravarty +- modified for GHC 4.04 + +* Wed Jun 30 1999 Manuel Chakravarty +- some more improvements from vbzoli + +* Fri Feb 26 1999 Manuel Chakravarty +- modified for GHC 4.02 + +* Thu Dec 24 1998 Zoltan Vorosbaranyi +- added BuildRoot +- files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib + +* Tue Jul 28 1998 Manuel Chakravarty +- original version diff --git a/ghc-doc-no-ps-install.patch b/ghc-doc-no-ps-install.patch new file mode 100644 index 0000000..e959aa1 --- /dev/null +++ b/ghc-doc-no-ps-install.patch @@ -0,0 +1,12 @@ +--- ghc-6.4/Makefile.in~ 2005-03-09 00:01:08.000000000 +0900 ++++ ghc-6.4/Makefile.in 2005-03-12 12:53:02.531724624 +0900 +@@ -274,9 +274,6 @@ + + install-docs : install-dirs-docs + if test -d share/html ; then $(CP) -r share/html/* $(htmldir) ; fi +- for i in share/*.ps; do \ +- $(CP) $$i $(psdir) ; \ +- done + + install-dirs-docs: + $(INSTALL_DIR) $(htmldir) diff --git a/ghc.spec b/ghc.spec index fad900d..19c4d6e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ Name: ghc Version: 6.4 -Release: 8 +Release: 8%{dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -171,6 +171,9 @@ fi %endif %changelog +* Tue May 31 2005 Jens Petersen +- add %%dist to release + * Thu May 12 2005 Jens Petersen - 6.4-8 - initial import into Fedora Extras diff --git a/sources b/sources index 39fe85b..1fc3de8 100644 --- a/sources +++ b/sources @@ -1 +1,4 @@ 45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 +89aaed2c09667f25a1777012a42200c7 ghc-6.4-i386-unknown-linux.tar.bz2 +6ad2f7df7f55e8cfec0504384bf664ea ghc-6.4-x86_64-unknown-linux.tar.bz2 +1400a1c158b07821f81ee5e4a7433b91 ghc-6.4-ppc-unknown-linux.tar.bz2 From 340d4c8b21e33c7e62925f9cbef6e96a1259cb9a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 2 Jun 2005 01:55:58 +0000 Subject: [PATCH 007/530] revert to non-bootstrap build --- .cvsignore | 3 - Makefile | 4 +- ghc-bootstrap.spec | 231 ------------------------------------ ghc-doc-no-ps-install.patch | 12 -- ghc.spec | 2 +- sources | 3 - 6 files changed, 2 insertions(+), 253 deletions(-) delete mode 100644 ghc-bootstrap.spec delete mode 100644 ghc-doc-no-ps-install.patch diff --git a/.cvsignore b/.cvsignore index cad5ac1..9cbb0e0 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,4 +1 @@ ghc-6.4-src.tar.bz2 -ghc-6.4-i386-unknown-linux.tar.bz2 -ghc-6.4-x86_64-unknown-linux.tar.bz2 -ghc-6.4-ppc-unknown-linux.tar.bz2 diff --git a/Makefile b/Makefile index d6abb41..d85df4e 100644 --- a/Makefile +++ b/Makefile @@ -1,9 +1,7 @@ # Makefile for source rpm: ghc # $Id$ NAME := ghc -#SPECFILE = $(firstword $(wildcard *.spec)) -# for bootstrap -SPECFILE = ghc-bootstrap.spec +SPECFILE = $(firstword $(wildcard *.spec)) define find-makefile-common for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done diff --git a/ghc-bootstrap.spec b/ghc-bootstrap.spec deleted file mode 100644 index a5d6f1c..0000000 --- a/ghc-bootstrap.spec +++ /dev/null @@ -1,231 +0,0 @@ -## ghc seeding bootstrap spec file - -%define ghcver ghc64 - -Name: ghc -Version: 6.4 -Release: 1%{?dist} -Summary: Glasgow Haskell Compilation system -License: BSD style -Group: Development/Languages -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-i386-unknown-linux.tar.bz2 -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-ppc-unknown-linux.tar.bz2 -Source3: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-x86_64-unknown-linux.tar.bz2 -URL: http://haskell.org/ghc/ -Requires: %{ghcver} = %{version}-%{release} -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -BuildRequires: sed -Prefix: %{_prefix} -Patch1: ghc-doc-no-ps-install.patch -ExclusiveArch: i386 ppc x86_64 - -%description -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interface. - -%package -n %{ghcver} -Summary: Documentation for GHC -Group: Development/Languages -Requires: gcc gmp-devel readline-devel - -%description -n %{ghcver} -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interfaces. - -This package contains all the main files and libraries of version %{version}. - -%package -n %{ghcver}-prof -Summary: Profiling libraries for GHC -Group: Development/Libraries -Requires: %{ghcver} = %{version}-%{release} -Obsoletes: ghc-prof - -%description -n %{ghcver}-prof -Profiling libraries for Glorious Glasgow Haskell Compilation System -(GHC). They should be installed when GHC's profiling subsystem is -needed. - -%package doc -Summary: Documentation for GHC -Group: Development/Languages - -%description doc -Preformatted documentation for the Glorious Glasgow Haskell -Compilation System (GHC) and its libraries. It should be installed if -you like to have local access to the documentation in HTML format. - -# the debuginfo subpackage is currently empty anyway, so don't generate it -%define debug_package %{nil} -%define __spec_install_post /usr/lib/rpm/brp-compress - -%prep -rm -rf %{name}-%{version} -tar jxf ${RPM_SOURCE_DIR}/%{name}-%{version}-%{_arch}-unknown-linux.tar.bz2 -%setup -T -D -%patch1 -p1 -b .ps - -%build -./configure --prefix=%{_prefix} --libdir=%{_libdir} -make prefix=%{_prefix} libdir=%{_libdir}/%{name}-%{version} - -%install -rm -rf $RPM_BUILD_ROOT - -make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} datadir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} htmldir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} install-dirs install-bin install-libs install-datas install-docs - -SRC_TOP=$PWD -rm -f rpm-*-filelist rpm-*.files -( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) -) - -# make paths absolute (filter "./usr" to "/usr") -sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files - -cat rpm-dir.files rpm-lib.files > rpm-base-filelist -cat rpm-dir.files rpm-prof.files > rpm-prof-filelist - -%clean -rm -rf $RPM_BUILD_ROOT - -%post -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} -fi - -%post -n %{ghcver} -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf -fi - -%files -%defattr(-,root,root,-) -%{_bindir}/* -%exclude %{_bindir}/ghc*%{version} - -%files -n %{ghcver} -f rpm-base-filelist -%defattr(-,root,root,-) -%doc ANNOUNCE LICENSE README -%{_bindir}/ghc*%{version} -%config(noreplace) %{_libdir}/ghc-%{version}/package.conf - -%files -n %{ghcver}-prof -f rpm-prof-filelist -%defattr(-,root,root,-) - -%files doc -%defattr(-,root,root,-) -%{_docdir}/%{name}-%{version} - -%changelog -* Tue May 31 2005 Jens Petersen -- initial seed bootstrap package for Fedora Extras for i386, ppc and x86_64 -- add %%dist to release - -* Thu May 12 2005 Jens Petersen -- add build_prof and build_doc switches for -doc and -prof subpackages - -* Wed May 11 2005 Jens Petersen -- make package relocatable (ghc#1084122) - - add post install scripts to replace prefix in driver scripts - -* Wed Mar 16 2005 Jens Petersen -- make ghc require ghcver of same ver-rel - -* Tue Mar 15 2005 Jens Petersen -- ghc requires ghcver (Amanda Clare) - -* Sat Mar 12 2005 Jens Petersen -- 6.4 release -- use sed instead of perl to tidy filelists -- no epoch for ghc64-prof's ghc64 requirement - -* Fri Jan 21 2005 Jens Petersen - 6.2.2-2 -- add x86_64 port - - build unregistered and without splitobjs - - specify libdir to configure and install -- rename ghc-prof to ghcXYZ-prof, which obsoletes ghc-prof - -* Mon Dec 6 2004 Jens Petersen - 6.2.2-1 -- move ghc requires to ghcXYZ - -* Wed Nov 24 2004 Jens Petersen - 6.2.2-0.fdr.1 -- ghc622 - - provide ghc = %%version -- require gcc, gmp-devel and readline-devel - -* Fri Oct 15 2004 Gerard Milmeister - 6.2.2-0.fdr.1 -- New Version 6.2.2 - -* Mon Mar 22 2004 Gerard Milmeister - 6.2.1-0.fdr.1 -- New Version 6.2.1 - -* Tue Dec 16 2003 Gerard Milmeister - 6.2-0.fdr.1 -- New Version 6.2 - -* Tue Dec 16 2003 Gerard Milmeister - 6.0.1-0.fdr.3 -- A few minor specfile tweaks - -* Mon Dec 15 2003 Gerard Milmeister - 6.0.1-0.fdr.2 -- Different file list generation - -* Mon Oct 20 2003 Gerard Milmeister - 6.0.1-0.fdr.1 -- First Fedora release -- Added generated html docs, so that haddock is not needed - -* Wed Sep 26 2001 Manuel Chakravarty -- small changes for 5.04 - -* Wed Sep 26 2001 Manuel Chakravarty -- split documentation off into a separate package -- adapt to new docbook setup in RH7.1 - -* Mon Apr 16 2001 Manuel Chakravarty -- revised for 5.00 -- also runs autoconf automagically if no ./configure found - -* Thu Jun 22 2000 Sven Panne -- removed explicit usage of hslibs/docs, it belongs to ghc/docs/set - -* Sun Apr 23 2000 Manuel Chakravarty -- revised for ghc 4.07; added suggestions from Pixel -- added profiling package - -* Tue Dec 7 1999 Manuel Chakravarty -- version for use from CVS - -* Thu Sep 16 1999 Manuel Chakravarty -- modified for GHC 4.04, patchlevel 1 (no more 62 tuple stuff); minimises use - of patch files - instead emits a build.mk on-the-fly - -* Sat Jul 31 1999 Manuel Chakravarty -- modified for GHC 4.04 - -* Wed Jun 30 1999 Manuel Chakravarty -- some more improvements from vbzoli - -* Fri Feb 26 1999 Manuel Chakravarty -- modified for GHC 4.02 - -* Thu Dec 24 1998 Zoltan Vorosbaranyi -- added BuildRoot -- files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib - -* Tue Jul 28 1998 Manuel Chakravarty -- original version diff --git a/ghc-doc-no-ps-install.patch b/ghc-doc-no-ps-install.patch deleted file mode 100644 index e959aa1..0000000 --- a/ghc-doc-no-ps-install.patch +++ /dev/null @@ -1,12 +0,0 @@ ---- ghc-6.4/Makefile.in~ 2005-03-09 00:01:08.000000000 +0900 -+++ ghc-6.4/Makefile.in 2005-03-12 12:53:02.531724624 +0900 -@@ -274,9 +274,6 @@ - - install-docs : install-dirs-docs - if test -d share/html ; then $(CP) -r share/html/* $(htmldir) ; fi -- for i in share/*.ps; do \ -- $(CP) $$i $(psdir) ; \ -- done - - install-dirs-docs: - $(INSTALL_DIR) $(htmldir) diff --git a/ghc.spec b/ghc.spec index 19c4d6e..d185a2d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ Name: ghc Version: 6.4 -Release: 8%{dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages diff --git a/sources b/sources index 1fc3de8..39fe85b 100644 --- a/sources +++ b/sources @@ -1,4 +1 @@ 45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 -89aaed2c09667f25a1777012a42200c7 ghc-6.4-i386-unknown-linux.tar.bz2 -6ad2f7df7f55e8cfec0504384bf664ea ghc-6.4-x86_64-unknown-linux.tar.bz2 -1400a1c158b07821f81ee5e4a7433b91 ghc-6.4-ppc-unknown-linux.tar.bz2 From af099c0af99980be42ed848a0de32b46b66099e5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 20 Sep 2005 23:37:16 +0000 Subject: [PATCH 008/530] - 6.4.1 release - the following patches are now upstream: ghc-6.4-powerpc.patch, rts-GCCompact.h-x86_64.patch, ghc-6.4-dsforeign-x86_64-1097471.patch, ghc-6.4-rts-adjustor-x86_64-1097471.patch - builds with gcc4 so drop %%_with_gcc32 - x86_64 build restrictions (no ghci and split objects) no longer apply --- .cvsignore | 2 +- ghc-6.4-dsforeign-x86_64-1097471.patch | 249 --------------------- ghc-6.4-powerpc.patch | 26 --- ghc-6.4-rts-adjustor-x86_64-1097471.patch | 250 ---------------------- ghc.spec | 33 ++- rts-GCCompact.h-x86_64.patch | 32 --- sources | 2 +- 7 files changed, 15 insertions(+), 579 deletions(-) delete mode 100644 ghc-6.4-dsforeign-x86_64-1097471.patch delete mode 100644 ghc-6.4-powerpc.patch delete mode 100644 ghc-6.4-rts-adjustor-x86_64-1097471.patch delete mode 100644 rts-GCCompact.h-x86_64.patch diff --git a/.cvsignore b/.cvsignore index 9cbb0e0..166a991 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1 @@ -ghc-6.4-src.tar.bz2 +ghc-6.4.1-src.tar.bz2 diff --git a/ghc-6.4-dsforeign-x86_64-1097471.patch b/ghc-6.4-dsforeign-x86_64-1097471.patch deleted file mode 100644 index 3ecbb88..0000000 --- a/ghc-6.4-dsforeign-x86_64-1097471.patch +++ /dev/null @@ -1,249 +0,0 @@ -diff -u ghc-6.4/ghc/compiler/deSugar/DsForeign.lhs ghc-6.5/ghc/compiler/deSugar/DsForeign.lhs ---- ghc-6.4/ghc/compiler/deSugar/DsForeign.lhs 2005-05-07 11:51:04.000000000 +0900 -+++ ghc-6.5/ghc/compiler/deSugar/DsForeign.lhs 2005-05-07 11:51:04.000000000 +0900 -@@ -24,14 +24,14 @@ - import Type ( isUnLiftedType ) - #endif - import MachOp ( machRepByteWidth, MachRep(..) ) --import SMRep ( argMachRep, primRepToCgRep ) -+import SMRep ( argMachRep, typeCgRep ) - import CoreUtils ( exprType, mkInlineMe ) - import Id ( Id, idType, idName, mkSysLocal, setInlinePragma ) - import Literal ( Literal(..), mkStringLit ) - import Module ( moduleString ) - import Name ( getOccString, NamedThing(..) ) - import OccName ( encodeFS ) --import Type ( repType, coreEqType, typePrimRep ) -+import Type ( repType, coreEqType ) - import TcType ( Type, mkFunTys, mkForAllTys, mkTyConApp, - mkFunTy, tcSplitTyConApp_maybe, - tcSplitForAllTys, tcSplitFunTys, tcTyConAppArgs, -@@ -52,7 +52,7 @@ - import BasicTypes ( Activation( NeverActive ) ) - import SrcLoc ( Located(..), unLoc ) - import Outputable --import Maybe ( fromJust ) -+import Maybe ( fromJust, isNothing ) - import FastString - \end{code} - -@@ -95,7 +95,7 @@ - combine (ForeignStubs acc_h acc_c acc_hdrs acc_feb, acc_f) - (L loc (ForeignExport (L _ id) _ (CExport (CExportStatic ext_nm cconv)) depr)) - = dsFExport id (idType id) -- ext_nm cconv False `thenDs` \(h, c, _) -> -+ ext_nm cconv False `thenDs` \(h, c, _, _) -> - warnDepr depr loc `thenDs` \_ -> - returnDs (ForeignStubs (h $$ acc_h) (c $$ acc_c) acc_hdrs (id:acc_feb), - acc_f) -@@ -292,7 +292,8 @@ - -- the first argument's stable pointer - -> DsM ( SDoc -- contents of Module_stub.h - , SDoc -- contents of Module_stub.c -- , [Type] -- primitive arguments expected by stub function. -+ , [MachRep] -- primitive arguments expected by stub function -+ , Int -- size of args to stub function - ) - - dsFExport fn_id ty ext_name cconv isDyn -@@ -371,7 +372,8 @@ - in - dsLookupGlobalId bindIOName `thenDs` \ bindIOId -> - newSysLocalDs stable_ptr_ty `thenDs` \ stbl_value -> -- dsFExport id export_ty fe_nm cconv True `thenDs` \ (h_code, c_code, stub_args) -> -+ dsFExport id export_ty fe_nm cconv True -+ `thenDs` \ (h_code, c_code, arg_reps, args_size) -> - let - stbl_app cont ret_ty = mkApps (Var bindIOId) - [ Type stable_ptr_ty -@@ -395,9 +397,7 @@ - -- (probably in the RTS.) - adjustor = FSLIT("createAdjustor") - -- arg_type_info = drop 2 $ map (repCharCode.argMachRep -- .primRepToCgRep.typePrimRep) -- stub_args -+ arg_type_info = map repCharCode arg_reps - repCharCode F32 = 'f' - repCharCode F64 = 'd' - repCharCode I64 = 'l' -@@ -407,17 +407,9 @@ - -- so that we can attach the '@N' suffix to its label if it is a - -- stdcall on Windows. - mb_sz_args = case cconv of -- StdCallConv -> Just (sum (map ty_size stub_args)) -+ StdCallConv -> Just args_size - _ -> Nothing - -- -- NB. the calculation here isn't strictly speaking correct. -- -- We have a primitive Haskell type (eg. Int#, Double#), and -- -- we want to know the size, when passed on the C stack, of -- -- the associated C type (eg. HsInt, HsDouble). We don't have -- -- this information to hand, but we know what GHC's conventions -- -- are for passing around the primitive Haskell types, so we -- -- use that instead. I hope the two coincide --SDM -- ty_size = machRepByteWidth.argMachRep.primRepToCgRep.typePrimRep - in - dsCCall adjustor adj_args PlayRisky io_res_ty `thenDs` \ ccall_adj -> - -- PlayRisky: the adjustor doesn't allocate in the Haskell heap or do a callback -@@ -464,33 +456,33 @@ - -> CCallConv - -> (SDoc, - SDoc, -- [Type] -- the *primitive* argument types -+ [MachRep], -- the argument reps -+ Int -- total size of arguments - ) - mkFExportCBits c_nm maybe_target arg_htys res_hty is_IO_res_ty cc -- = (header_bits, c_bits, all_prim_arg_tys) -+ = (header_bits, c_bits, -+ [rep | (_,_,_,rep) <- arg_info], -- just the real args -+ sum [ machRepByteWidth rep | (_,_,_,rep) <- aug_arg_info] -- all the args -+ ) - where -- -- Create up types and names for the real args -- arg_cnames, arg_ctys :: [SDoc] -- arg_cnames = mkCArgNames 1 arg_htys -- arg_ctys = map showStgType arg_htys -- -- -- and also for auxiliary ones; the stable ptr in the dynamic case, and -- -- a slot for the dummy return address in the dynamic + ccall case -- extra_cnames_and_tys -- = case maybe_target of -- Nothing -> [((text "the_stableptr", text "StgStablePtr"), mkStablePtrPrimTy alphaTy)] -- other -> [] -- ++ -- case (maybe_target, cc) of -- (Nothing, CCallConv) -> [((text "original_return_addr", text "void*"), addrPrimTy)] -- other -> [] -- -- all_cnames_and_ctys :: [(SDoc, SDoc)] -- all_cnames_and_ctys -- = map fst extra_cnames_and_tys ++ zip arg_cnames arg_ctys -- -- all_prim_arg_tys -- = map snd extra_cnames_and_tys ++ map getPrimTyOf arg_htys -+ -- list the arguments to the C function -+ arg_info :: [(SDoc, -- arg name -+ SDoc, -- C type -+ Type, -- Haskell type -+ MachRep)] -- the MachRep -+ arg_info = [ (text ('a':show n), showStgType ty, ty, -+ typeMachRep (getPrimTyOf ty)) -+ | (ty,n) <- zip arg_htys [1..] ] -+ -+ -- add some auxiliary args; the stable ptr in the wrapper case, and -+ -- a slot for the dummy return address in the wrapper + ccall case -+ aug_arg_info -+ | isNothing maybe_target = stable_ptr_arg : insertRetAddr cc arg_info -+ | otherwise = arg_info -+ -+ stable_ptr_arg = -+ (text "the_stableptr", text "StgStablePtr", undefined, -+ typeMachRep (mkStablePtrPrimTy alphaTy)) - - -- stuff to do with the return type of the C function - res_hty_is_unit = res_hty `coreEqType` unitTy -- Look through any newtypes -@@ -506,8 +498,8 @@ - header_bits = ptext SLIT("extern") <+> fun_proto <> semi - - fun_proto = cResType <+> pprCconv <+> ftext c_nm <> -- parens (hsep (punctuate comma (map (\(nm,ty) -> ty <+> nm) -- all_cnames_and_ctys))) -+ parens (hsep (punctuate comma (map (\(nm,ty,_,_) -> ty <+> nm) -+ aug_arg_info))) - - -- the target which will form the root of what we ask rts_evalIO to run - the_cfun -@@ -517,9 +509,9 @@ - - -- the expression we give to rts_evalIO - expr_to_run -- = foldl appArg the_cfun (zip arg_cnames arg_htys) -+ = foldl appArg the_cfun arg_info -- NOT aug_arg_info - where -- appArg acc (arg_cname, arg_hty) -+ appArg acc (arg_cname, _, arg_hty, _) - = text "rts_apply" - <> parens (acc <> comma <> mkHObj arg_hty <> parens arg_cname) - -@@ -538,6 +530,30 @@ - Nothing -> empty - Just hs_fn -> text "extern StgClosure " <> ppr hs_fn <> text "_closure" <> semi - -+ -- the only reason for making the mingw32 (anything targetting PE, really) stick -+ -- out here is that the GHCi linker isn't capable of handling .ctors sections -+ useStaticConstructors -+#if defined(mingw32_HOST_OS) -+ = False -+#else -+ = True -+#endif -+ -+ initialiser -+ = case maybe_target of -+ Nothing -> empty -+ Just hs_fn -+ | not useStaticConstructors -> empty -+ | otherwise -> -+ vcat -+ [ text "static void stginit_export_" <> ppr hs_fn -+ <> text "() __attribute__((constructor));" -+ , text "static void stginit_export_" <> ppr hs_fn <> text "()" -+ , braces (text "getStablePtr" -+ <> parens (text "(StgPtr) &" <> ppr hs_fn <> text "_closure") -+ <> semi) -+ ] -+ - -- finally, the whole darn thing - c_bits = - space $$ -@@ -568,11 +584,17 @@ - , if res_hty_is_unit then empty - else text "return cret;" - , rbrace -- ] -- -+ ] $$ -+ initialiser - --mkCArgNames :: Int -> [a] -> [SDoc] --mkCArgNames n as = zipWith (\ _ n -> text ('a':show n)) as [n..] -+-- NB. the calculation here isn't strictly speaking correct. -+-- We have a primitive Haskell type (eg. Int#, Double#), and -+-- we want to know the size, when passed on the C stack, of -+-- the associated C type (eg. HsInt, HsDouble). We don't have -+-- this information to hand, but we know what GHC's conventions -+-- are for passing around the primitive Haskell types, so we -+-- use that instead. I hope the two coincide --SDM -+typeMachRep ty = argMachRep (typeCgRep ty) - - mkHObj :: Type -> SDoc - mkHObj t = text "rts_mk" <> text (showFFIType t) -@@ -590,6 +612,26 @@ - Just (tc,_) -> tc - Nothing -> pprPanic "showFFIType" (ppr t) - -+#if !defined(x86_64_TARGET_ARCH) -+insertRetAddr CCallConv args = ret_addr_arg : args -+insertRetAddr _ args = args -+#else -+-- On x86_64 we insert the return address after the 6th -+-- integer argument, because this is the point at which we -+-- need to flush a register argument to the stack (See rts/Adjustor.c for -+-- details). -+insertRetAddr CCallConv args = go 0 args -+ where go 6 args = ret_addr_arg : args -+ go n (arg@(_,_,_,rep):args) -+ | I64 <- rep = arg : go (n+1) args -+ | otherwise = arg : go n args -+ go n [] = [] -+insertRetAddr _ args = args -+#endif -+ -+ret_addr_arg = (text "original_return_addr", text "void*", undefined, -+ typeMachRep addrPrimTy) -+ - -- This function returns the primitive type associated with the boxed - -- type argument to a foreign export (eg. Int ==> Int#). It assumes - -- that all the types we are interested in have a single constructor diff --git a/ghc-6.4-powerpc.patch b/ghc-6.4-powerpc.patch deleted file mode 100644 index 7fc7ccd..0000000 --- a/ghc-6.4-powerpc.patch +++ /dev/null @@ -1,26 +0,0 @@ -diff -ur ghc-6.4/distrib/configure-bin.ac ghc-6.4/distrib/configure-bin.ac ---- ghc-6.4/distrib/configure-bin.ac 2005-03-10 09:10:09.000000000 -0500 -+++ ghc-6.4/distrib/configure-bin.ac 2005-03-14 21:37:20.356380744 -0500 -@@ -78,6 +78,10 @@ - TargetPlatform=rs6000-ibm-aix;; - powerpc-apple-darwin*) - TargetPlatform=powerpc-apple-darwin;; -+powerpc-*-linux*) -+ TargetPlatform=powerpc-unknown-linux;; -+powerpc64-*-linux*) -+ TargetPlatform=powerpc64-unknown-linux;; - sparc-sun-sunos4*) - TargetPlatform=sparc-sun-sunos4;; - sparc-sun-solaris2*) -diff -ur ghc-6.4/ghc/includes/MachRegs.h ghc-6.4/ghc/includes/MachRegs.h ---- ghc-6.4/ghc/includes/MachRegs.h 2005-01-28 07:55:51.000000000 -0500 -+++ ghc-6.4/ghc/includes/MachRegs.h 2005-03-14 21:37:31.825368128 -0500 -@@ -457,7 +457,7 @@ - #define REG_R7 r20 - #define REG_R8 r21 - --#ifdef darwin_REGS -+#if darwin_REGS - - #define REG_F1 f14 - #define REG_F2 f15 diff --git a/ghc-6.4-rts-adjustor-x86_64-1097471.patch b/ghc-6.4-rts-adjustor-x86_64-1097471.patch deleted file mode 100644 index c77260d..0000000 --- a/ghc-6.4-rts-adjustor-x86_64-1097471.patch +++ /dev/null @@ -1,250 +0,0 @@ -diff -u ghc-6.4/ghc/rts/Adjustor.c ghc-6.5/ghc/rts/Adjustor.c ---- ghc-6.4/ghc/rts/Adjustor.c 2005-05-07 11:46:10.000000000 +0900 -+++ ghc-6.5/ghc/rts/Adjustor.c 2005-05-07 11:46:11.000000000 +0900 -@@ -46,13 +46,18 @@ - #include - #endif - --#if defined(openbsd_HOST_OS) -+#if defined(openbsd_HOST_OS) || defined(linux_HOST_OS) - #include - #include - #include - - /* no C99 header stdint.h on OpenBSD? */ -+#if defined(openbsd_HOST_OS) - typedef unsigned long my_uintptr_t; -+#else -+#include -+typedef uintptr_t my_uintptr_t; -+#endif - #endif - - #if defined(powerpc_HOST_ARCH) && defined(linux_HOST_OS) -@@ -80,7 +85,7 @@ - barf("mallocBytesRWX: failed to protect 0x%p; error=%lu; old protection: %lu\n", - addr, (unsigned long)GetLastError(), (unsigned long)dwOldProtect); - } --#elif defined(openbsd_HOST_OS) -+#elif defined(openbsd_HOST_OS) || defined(linux_HOST_OS) - /* malloced memory isn't executable by default on OpenBSD */ - my_uintptr_t pageSize = sysconf(_SC_PAGESIZE); - my_uintptr_t mask = ~(pageSize - 1); -@@ -94,8 +99,46 @@ - return addr; - } - -+#ifdef LEADING_UNDERSCORE -+#define UNDERSCORE "_" -+#else -+#define UNDERSCORE "" -+#endif - #if defined(i386_HOST_ARCH) --static unsigned char *obscure_ccall_ret_code; -+/* -+ Now here's something obscure for you: -+ -+ When generating an adjustor thunk that uses the C calling -+ convention, we have to make sure that the thunk kicks off -+ the process of jumping into Haskell with a tail jump. Why? -+ Because as a result of jumping in into Haskell we may end -+ up freeing the very adjustor thunk we came from using -+ freeHaskellFunctionPtr(). Hence, we better not return to -+ the adjustor code on our way out, since it could by then -+ point to junk. -+ -+ The fix is readily at hand, just include the opcodes -+ for the C stack fixup code that we need to perform when -+ returning in some static piece of memory and arrange -+ to return to it before tail jumping from the adjustor thunk. -+*/ -+__asm__ ( -+ ".globl " UNDERSCORE "obscure_ccall_ret_code\n" -+ UNDERSCORE "obscure_ccall_ret_code:\n\t" -+ "addl $0x4, %esp\n\t" -+ "ret" -+ ); -+extern void obscure_ccall_ret_code(void); -+#endif -+ -+#if defined(x86_64_HOST_ARCH) -+__asm__ ( -+ ".globl " UNDERSCORE "obscure_ccall_ret_code\n" -+ UNDERSCORE "obscure_ccall_ret_code:\n\t" -+ "addq $0x8, %rsp\n\t" -+ "ret" -+ ); -+extern void obscure_ccall_ret_code(void); - #endif - - #if defined(alpha_HOST_ARCH) -@@ -195,7 +238,7 @@ - createAdjustor(int cconv, StgStablePtr hptr, - StgFunPtr wptr, - char *typeString --#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) -+#if !defined(powerpc_HOST_ARCH) && !defined(powerpc64_HOST_ARCH) && !defined(x86_64_HOST_ARCH) - STG_UNUSED - #endif - ) -@@ -279,6 +322,111 @@ - adj_code[0x0f] = (unsigned char)0xff; /* jmp *%eax */ - adj_code[0x10] = (unsigned char)0xe0; - } -+#elif defined(x86_64_HOST_ARCH) -+ /* -+ stack at call: -+ argn -+ ... -+ arg7 -+ return address -+ %rdi,%rsi,%rdx,%rcx,%r8,%r9 = arg0..arg6 -+ -+ if there are <6 integer args, then we can just push the -+ StablePtr into %edi and shuffle the other args up. -+ -+ If there are >=6 integer args, then we have to flush one arg -+ to the stack, and arrange to adjust the stack ptr on return. -+ The stack will be rearranged to this: -+ -+ argn -+ ... -+ arg7 -+ return address *** <-- dummy arg in stub fn. -+ arg6 -+ obscure_ccall_ret_code -+ -+ This unfortunately means that the type of the stub function -+ must have a dummy argument for the original return address -+ pointer inserted just after the 6th integer argument. -+ -+ Code for the simple case: -+ -+ 0: 4d 89 c1 mov %r8,%r9 -+ 3: 49 89 c8 mov %rcx,%r8 -+ 6: 48 89 d1 mov %rdx,%rcx -+ 9: 48 89 f2 mov %rsi,%rdx -+ c: 48 89 fe mov %rdi,%rsi -+ f: 48 8b 3d 0a 00 00 00 mov 10(%rip),%rdi -+ 16: e9 00 00 00 00 jmpq stub_function -+ ... -+ 20: .quad 0 # aligned on 8-byte boundary -+ -+ -+ And the version for >=6 integer arguments: -+ -+ 0: 41 51 push %r9 -+ 2: 68 00 00 00 00 pushq $obscure_ccall_ret_code -+ 7: 4d 89 c1 mov %r8,%r9 -+ a: 49 89 c8 mov %rcx,%r8 -+ d: 48 89 d1 mov %rdx,%rcx -+ 10: 48 89 f2 mov %rsi,%rdx -+ 13: 48 89 fe mov %rdi,%rsi -+ 16: 48 8b 3d 0b 00 00 00 mov 11(%rip),%rdi -+ 1d: e9 00 00 00 00 jmpq stub_function -+ ... -+ 28: .quad 0 # aligned on 8-byte boundary -+ */ -+ -+ /* we assume the small code model (gcc -mcmmodel=small) where -+ * all symbols are <2^32, so hence wptr should fit into 32 bits. -+ */ -+ ASSERT(((long)wptr >> 32) == 0); -+ -+ { -+ int i = 0; -+ char *c; -+ -+ // determine whether we have 6 or more integer arguments, -+ // and therefore need to flush one to the stack. -+ for (c = typeString; *c != '\0'; c++) { -+ if (*c == 'i' || *c == 'l') i++; -+ if (i == 6) break; -+ } -+ -+ if (i < 6) { -+ adjustor = mallocBytesRWX(40); -+ -+ *(StgInt32 *)adjustor = 0x49c1894d; -+ *(StgInt32 *)(adjustor+4) = 0x8948c889; -+ *(StgInt32 *)(adjustor+8) = 0xf28948d1; -+ *(StgInt32 *)(adjustor+12) = 0x48fe8948; -+ *(StgInt32 *)(adjustor+16) = 0x000a3d8b; -+ *(StgInt32 *)(adjustor+20) = 0x00e90000; -+ -+ *(StgInt32 *)(adjustor+23) = -+ (StgInt32)((StgInt64)wptr - (StgInt64)adjustor - 27); -+ *(StgInt64 *)(adjustor+32) = (StgInt64)hptr; -+ } -+ else -+ { -+ adjustor = mallocBytesRWX(48); -+ -+ *(StgInt32 *)adjustor = 0x00685141; -+ *(StgInt32 *)(adjustor+4) = 0x4d000000; -+ *(StgInt32 *)(adjustor+8) = 0x8949c189; -+ *(StgInt32 *)(adjustor+12) = 0xd18948c8; -+ *(StgInt32 *)(adjustor+16) = 0x48f28948; -+ *(StgInt32 *)(adjustor+20) = 0x8b48fe89; -+ *(StgInt32 *)(adjustor+24) = 0x00000b3d; -+ *(StgInt32 *)(adjustor+28) = 0x0000e900; -+ -+ *(StgInt32 *)(adjustor+3) = -+ (StgInt32)(StgInt64)obscure_ccall_ret_code; -+ *(StgInt32 *)(adjustor+30) = -+ (StgInt32)((StgInt64)wptr - (StgInt64)adjustor - 34); -+ *(StgInt64 *)(adjustor+40) = (StgInt64)hptr; -+ } -+ } - #elif defined(sparc_HOST_ARCH) - /* Magic constant computed by inspecting the code length of the following - assembly language snippet (offset and machine code prefixed): -@@ -848,7 +996,16 @@ - freeStablePtr(*((StgStablePtr*)((unsigned char*)ptr + 0x01))); - } else { - freeStablePtr(*((StgStablePtr*)((unsigned char*)ptr + 0x02))); -- } -+ } -+#elif defined(x86_64_HOST_ARCH) -+ if ( *(StgWord16 *)ptr == 0x894d ) { -+ freeStablePtr(*(StgStablePtr*)(ptr+32)); -+ } else if ( *(StgWord16 *)ptr == 0x5141 ) { -+ freeStablePtr(*(StgStablePtr*)(ptr+40)); -+ } else { -+ errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); -+ return; -+ } - #elif defined(sparc_HOST_ARCH) - if ( *(unsigned long*)ptr != 0x9C23A008UL ) { - errorBelch("freeHaskellFunctionPtr: not for me, guv! %p\n", ptr); -@@ -906,30 +1063,4 @@ - void - initAdjustor(void) - { --#if defined(i386_HOST_ARCH) -- /* Now here's something obscure for you: -- -- When generating an adjustor thunk that uses the C calling -- convention, we have to make sure that the thunk kicks off -- the process of jumping into Haskell with a tail jump. Why? -- Because as a result of jumping in into Haskell we may end -- up freeing the very adjustor thunk we came from using -- freeHaskellFunctionPtr(). Hence, we better not return to -- the adjustor code on our way out, since it could by then -- point to junk. -- -- The fix is readily at hand, just include the opcodes -- for the C stack fixup code that we need to perform when -- returning in some static piece of memory and arrange -- to return to it before tail jumping from the adjustor thunk. -- */ -- -- obscure_ccall_ret_code = mallocBytesRWX(4); -- -- obscure_ccall_ret_code[0x00] = (unsigned char)0x83; /* addl $0x4, %esp */ -- obscure_ccall_ret_code[0x01] = (unsigned char)0xc4; -- obscure_ccall_ret_code[0x02] = (unsigned char)0x04; -- -- obscure_ccall_ret_code[0x03] = (unsigned char)0xc3; /* ret */ --#endif - } diff --git a/ghc.spec b/ghc.spec index d185a2d..58346a4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,16 +1,13 @@ %define build_version 6.4 -%define ghcver ghc64 +%define ghcver ghc641 # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 0 -# ghc-6.4 doesn't build with gcc-4.0 yet -%define _with_gcc32 %{nil} - Name: ghc -Version: 6.4 -Release: 8%{?dist} +Version: 6.4.1 +Release: 0.1%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -18,17 +15,13 @@ Source: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -BuildRequires: sed, %{ghcver}, %{?_with_gcc32: compat-gcc-32} +BuildRequires: ghc, sed Buildrequires: gmp-devel, readline-devel, xorg-x11-devel, freeglut-devel, openal-devel %if %{build_doc} # haddock generates libraries/ docs Buildrequires: libxslt, docbook-style-xsl, haddock %endif Prefix: %{_prefix} -Patch1: ghc-6.4-powerpc.patch -Patch2: rts-GCCompact.h-x86_64.patch -Patch3: ghc-6.4-dsforeign-x86_64-1097471.patch -Patch4: ghc-6.4-rts-adjustor-x86_64-1097471.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -85,22 +78,14 @@ you like to have local access to the documentation in HTML format. %prep %setup -q -n ghc-%{version} -%patch1 -p1 -b .1-ppc -%patch2 -p1 -b .2-x86_64 -%patch3 -p1 -b .3-x86_64 -%patch4 -p1 -b .4-x86_64 %build -%ifarch x86_64 -echo "SplitObjs = NO" >> mk/build.mk -echo "GhcWithInterpreter = NO" >> mk/build.mk -%endif %if !%{build_prof} echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif -./configure --prefix=%{_prefix} --libdir=%{_libdir} --with-ghc=ghc-%{build_version} %{?_with_gcc32: --with-gcc=%{_bindir}/gcc32} +./configure --prefix=%{_prefix} --libdir=%{_libdir} --with-ghc=ghc-%{build_version} make all %if %{build_doc} @@ -171,6 +156,14 @@ fi %endif %changelog +* Tue Sep 20 2005 Jens Petersen - 6.4.1-0 +- 6.4.1 release + - the following patches are now upstream: ghc-6.4-powerpc.patch, + rts-GCCompact.h-x86_64.patch, ghc-6.4-dsforeign-x86_64-1097471.patch, + ghc-6.4-rts-adjustor-x86_64-1097471.patch + - builds with gcc4 so drop %%_with_gcc32 + - x86_64 build restrictions (no ghci and split objects) no longer apply + * Tue May 31 2005 Jens Petersen - add %%dist to release diff --git a/rts-GCCompact.h-x86_64.patch b/rts-GCCompact.h-x86_64.patch deleted file mode 100644 index b640508..0000000 --- a/rts-GCCompact.h-x86_64.patch +++ /dev/null @@ -1,32 +0,0 @@ ---- fptools/ghc/rts/GCCompact.h 2004/09/12 11:27:14 1.4 -+++ fptools/ghc/rts/GCCompact.h 2005/04/29 16:18:58 1.5 -@@ -12,7 +12,7 @@ mark(StgPtr p, bdescr *bd) - nat offset_within_block = p - bd->start; // in words - StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); -- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); -+ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); - *bitmap_word |= bit_mask; - } - -@@ -22,17 +22,17 @@ unmark(StgPtr p, bdescr *bd) - nat offset_within_block = p - bd->start; // in words - StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); -- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); -+ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); - *bitmap_word &= ~bit_mask; - } - --INLINE_HEADER int -+INLINE_HEADER StgWord - is_marked(StgPtr p, bdescr *bd) - { - nat offset_within_block = p - bd->start; // in words - StgPtr bitmap_word = (StgPtr)bd->u.bitmap + - (offset_within_block / (sizeof(W_)*BITS_PER_BYTE)); -- nat bit_mask = 1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); -+ StgWord bit_mask = (StgWord)1 << (offset_within_block & (sizeof(W_)*BITS_PER_BYTE - 1)); - return (*bitmap_word & bit_mask); - } - diff --git a/sources b/sources index 39fe85b..46644af 100644 --- a/sources +++ b/sources @@ -1 +1 @@ -45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 +fd289bc7c3afa272ff831a71a50b5b00 ghc-6.4.1-src.tar.bz2 From 824ff1734d3ca3a894bf0d3a9c9f7ebd8c0d5880 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 20 Sep 2005 23:38:34 +0000 Subject: [PATCH 009/530] bump release --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 58346a4..4e09545 100644 --- a/ghc.spec +++ b/ghc.spec @@ -7,7 +7,7 @@ Name: ghc Version: 6.4.1 -Release: 0.1%{?dist} +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -156,7 +156,7 @@ fi %endif %changelog -* Tue Sep 20 2005 Jens Petersen - 6.4.1-0 +* Tue Sep 20 2005 Jens Petersen - 6.4.1-1 - 6.4.1 release - the following patches are now upstream: ghc-6.4-powerpc.patch, rts-GCCompact.h-x86_64.patch, ghc-6.4-dsforeign-x86_64-1097471.patch, From 3c45d5400c7e2dfbceaa4fdcc11b5f57a42056d7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 3 Oct 2005 02:46:03 +0000 Subject: [PATCH 010/530] turn on build_doc since haddock is now in Extras --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 4e09545..deff14d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -3,7 +3,7 @@ # speed up test builds by not building profiled libraries %define build_prof 1 -%define build_doc 0 +%define build_doc 1 Name: ghc Version: 6.4.1 @@ -156,6 +156,9 @@ fi %endif %changelog +* Mon Oct 3 2005 Jens Petersen +- turn on build_doc since haddock is now in Extras + * Tue Sep 20 2005 Jens Petersen - 6.4.1-1 - 6.4.1 release - the following patches are now upstream: ghc-6.4-powerpc.patch, From 1ae0da02b7930d13684a76d58609557bb37ff880 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 11 Oct 2005 03:05:07 +0000 Subject: [PATCH 011/530] =?UTF-8?q?-=20turn=20on=20build=5Fdoc=20since=20h?= =?UTF-8?q?addock=20is=20now=20in=20Extras=20-=20no=20longer=20specify=20g?= =?UTF-8?q?hc=20version=20to=20build=20with=20(Ville=20Skytt=C3=A4,=20#170?= =?UTF-8?q?176)?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- ghc.spec | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index deff14d..56a1c84 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,3 @@ -%define build_version 6.4 %define ghcver ghc641 # speed up test builds by not building profiled libraries @@ -7,7 +6,7 @@ Name: ghc Version: 6.4.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -85,7 +84,7 @@ echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif -./configure --prefix=%{_prefix} --libdir=%{_libdir} --with-ghc=ghc-%{build_version} +./configure --prefix=%{_prefix} --libdir=%{_libdir} make all %if %{build_doc} @@ -156,8 +155,9 @@ fi %endif %changelog -* Mon Oct 3 2005 Jens Petersen +* Tue Oct 11 2005 Jens Petersen - 6.4.1-2 - turn on build_doc since haddock is now in Extras +- no longer specify ghc version to build with (Ville Skyttä, #170176) * Tue Sep 20 2005 Jens Petersen - 6.4.1-1 - 6.4.1 release From c12a20f95011903fbc62afdbc38241aa8418ce9a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 2 Mar 2006 08:40:15 +0000 Subject: [PATCH 012/530] - buildrequire libX11-devel instead of xorg-x11-devel (Kevin Fenzi, #181024) - make ghc-doc require ghc (Michel Salim, #180449) --- ghc.spec | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 56a1c84..333548d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,7 +6,7 @@ Name: ghc Version: 6.4.1 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -15,7 +15,7 @@ URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) BuildRequires: ghc, sed -Buildrequires: gmp-devel, readline-devel, xorg-x11-devel, freeglut-devel, openal-devel +Buildrequires: gmp-devel, readline-devel, libX11-devel, freeglut-devel, openal-devel %if %{build_doc} # haddock generates libraries/ docs Buildrequires: libxslt, docbook-style-xsl, haddock @@ -65,6 +65,7 @@ needed. %package doc Summary: Documentation for GHC Group: Development/Languages +Requires: %{name} %description doc Preformatted documentation for the Glorious Glasgow Haskell @@ -155,6 +156,10 @@ fi %endif %changelog +* Thu Mar 2 2006 Jens Petersen - 6.4.1-3 +- buildrequire libX11-devel instead of xorg-x11-devel (Kevin Fenzi, #181024) +- make ghc-doc require ghc (Michel Salim, #180449) + * Tue Oct 11 2005 Jens Petersen - 6.4.1-2 - turn on build_doc since haddock is now in Extras - no longer specify ghc version to build with (Ville Skyttä, #170176) From 9c5a6c23e182e194c3d047ea86457b25e8d1ca97 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 21 Apr 2006 07:59:27 +0000 Subject: [PATCH 013/530] update to 6.4.2 release --- .cvsignore | 2 +- ghc.spec | 19 +++++++++++-------- sources | 2 +- 3 files changed, 13 insertions(+), 10 deletions(-) diff --git a/.cvsignore b/.cvsignore index 166a991..b512e86 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1 @@ -ghc-6.4.1-src.tar.bz2 +ghc-6.4.2-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 333548d..c0301e6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,12 @@ -%define ghcver ghc641 +%define ghcver ghc642 # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 1 Name: ghc -Version: 6.4.1 -Release: 3%{?dist} +Version: 6.4.2 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -14,8 +14,8 @@ Source: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -BuildRequires: ghc, sed -Buildrequires: gmp-devel, readline-devel, libX11-devel, freeglut-devel, openal-devel +BuildRequires: ghc, sed +Buildrequires: gmp-devel, readline-devel, libX11-devel, freeglut-devel, openal-devel %if %{build_doc} # haddock generates libraries/ docs Buildrequires: libxslt, docbook-style-xsl, haddock @@ -156,15 +156,18 @@ fi %endif %changelog -* Thu Mar 2 2006 Jens Petersen - 6.4.1-3 +* Thu Apr 20 2006 Jens Petersen - 6.4.2-1 +- update to 6.4.2 release + +* Thu Mar 2 2006 Jens Petersen - 6.4.1-3.fc5 - buildrequire libX11-devel instead of xorg-x11-devel (Kevin Fenzi, #181024) - make ghc-doc require ghc (Michel Salim, #180449) -* Tue Oct 11 2005 Jens Petersen - 6.4.1-2 +* Tue Oct 11 2005 Jens Petersen - 6.4.1-2.fc5 - turn on build_doc since haddock is now in Extras - no longer specify ghc version to build with (Ville Skyttä, #170176) -* Tue Sep 20 2005 Jens Petersen - 6.4.1-1 +* Tue Sep 20 2005 Jens Petersen - 6.4.1-1.fc5 - 6.4.1 release - the following patches are now upstream: ghc-6.4-powerpc.patch, rts-GCCompact.h-x86_64.patch, ghc-6.4-dsforeign-x86_64-1097471.patch, diff --git a/sources b/sources index 46644af..e83fb16 100644 --- a/sources +++ b/sources @@ -1 +1 @@ -fd289bc7c3afa272ff831a71a50b5b00 ghc-6.4.1-src.tar.bz2 +a394bf14e94c3bca5507d568fcc03375 ghc-6.4.2-src.tar.bz2 From 64398adc4aca560e750d637ad5869f4276f3d28c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 29 Apr 2006 07:33:52 +0000 Subject: [PATCH 014/530] - buildrequire libXt-devel so that the X11 package and deps get built (Garrett Mitchener, #190201) --- ghc.spec | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index c0301e6..d86b275 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,7 +6,7 @@ Name: ghc Version: 6.4.2 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -15,12 +15,14 @@ URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) BuildRequires: ghc, sed -Buildrequires: gmp-devel, readline-devel, libX11-devel, freeglut-devel, openal-devel +Buildrequires: gmp-devel, readline-devel +Buildrequires: libX11-devel, libXt-devel +Buildrequires: freeglut-devel, openal-devel %if %{build_doc} -# haddock generates libraries/ docs +# haddock generates docs in libraries Buildrequires: libxslt, docbook-style-xsl, haddock %endif -Prefix: %{_prefix} +Prefix: %{_prefix} %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -156,7 +158,11 @@ fi %endif %changelog -* Thu Apr 20 2006 Jens Petersen - 6.4.2-1 +* Sat Apr 29 2006 Jens Petersen - 6.4.2-2.fc6 +- buildrequire libXt-devel so that the X11 package and deps get built + (Garrett Mitchener, #190201) + +* Thu Apr 20 2006 Jens Petersen - 6.4.2-1.fc6 - update to 6.4.2 release * Thu Mar 2 2006 Jens Petersen - 6.4.1-3.fc5 From e54329f9b75fe4329cf254d432d7d71ae6b63e47 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Ville=20Skytt=C3=A4?= Date: Sun, 27 Aug 2006 20:26:18 +0000 Subject: [PATCH 015/530] http://fedoraproject.org/wiki/Extras/Schedule/FC6MassRebuild --- needs.rebuild | 1 + 1 file changed, 1 insertion(+) create mode 100644 needs.rebuild diff --git a/needs.rebuild b/needs.rebuild new file mode 100644 index 0000000..815fd29 --- /dev/null +++ b/needs.rebuild @@ -0,0 +1 @@ +http://fedoraproject.org/wiki/Extras/Schedule/FC6MassRebuild From 889645708cbaba0e1367fce658048488fc4f87cc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 25 Sep 2006 10:05:59 +0000 Subject: [PATCH 016/530] =?UTF-8?q?-=20ghost=20package.conf.old=20(G=C3=A9?= =?UTF-8?q?rard=20Milmeister)=20-=20set=20unconfined=5Fexecmem=5Fexec=5Ft?= =?UTF-8?q?=20context=20on=20executables=20with=20ghc=20rts=20=20=20=20=20?= =?UTF-8?q?(#195821)?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- ghc.spec | 22 +++++++++++++++++++++- 1 file changed, 21 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d86b275..c5e12b9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,7 +6,7 @@ Name: ghc Version: 6.4.2 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -117,9 +117,14 @@ cat rpm-dir.files rpm-lib.files > rpm-base-filelist cat rpm-dir.files rpm-prof.files > rpm-prof-filelist %endif +# create package.conf.old +touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old + + %clean rm -rf $RPM_BUILD_ROOT + %post ## tweak prefix in drivers scripts if relocating if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then @@ -127,6 +132,9 @@ if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} fi +/usr/bin/chcon -t unconfined_execmem_exec_t %{_bindir}/{hasktags,runghc,runhaskell} >/dev/null 2>&1 || : + + %post -n %{ghcver} ## tweak prefix in drivers scripts if relocating if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then @@ -135,29 +143,41 @@ if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf fi +/usr/bin/chcon -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/{ghc-%{version},ghc-pkg.bin,hsc2hs-bin} >/dev/null 2>&1 || : + + %files %defattr(-,root,root,-) %{_bindir}/* %exclude %{_bindir}/ghc*%{version} + %files -n %{ghcver} -f rpm-base-filelist %defattr(-,root,root,-) %doc ghc/ANNOUNCE ghc/LICENSE ghc/README %{_bindir}/ghc*%{version} %config(noreplace) %{_libdir}/ghc-%{version}/package.conf +%ghost %{_libdir}/ghc-%{version}/package.conf.old + %if %{build_prof} %files -n %{ghcver}-prof -f rpm-prof-filelist %defattr(-,root,root,-) %endif + %if %{build_doc} %files doc %defattr(-,root,root,-) %{_docdir}/%{name}-%{version} %endif + %changelog +* Mon Sep 25 2006 Jens Petersen - 6.4.2-3.fc6 +- ghost package.conf.old (Gérard Milmeister) +- set unconfined_execmem_exec_t context on executables with ghc rts (#195821) + * Sat Apr 29 2006 Jens Petersen - 6.4.2-2.fc6 - buildrequire libXt-devel so that the X11 package and deps get built (Garrett Mitchener, #190201) From a97ca19f8f0ba2a77a62af8d6c987c5089472de7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 25 Sep 2006 13:28:47 +0000 Subject: [PATCH 017/530] turn off building docs until haddock is back --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c5e12b9..c166781 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,7 +2,7 @@ # speed up test builds by not building profiled libraries %define build_prof 1 -%define build_doc 1 +%define build_doc 0 Name: ghc Version: 6.4.2 @@ -177,6 +177,7 @@ fi * Mon Sep 25 2006 Jens Petersen - 6.4.2-3.fc6 - ghost package.conf.old (Gérard Milmeister) - set unconfined_execmem_exec_t context on executables with ghc rts (#195821) +- turn off building docs until haddock is back * Sat Apr 29 2006 Jens Petersen - 6.4.2-2.fc6 - buildrequire libXt-devel so that the X11 package and deps get built From d9e09e981bb13bbab27c9d5cee96cd6f134da1e7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 27 Sep 2006 12:04:46 +0000 Subject: [PATCH 018/530] rebootstrap with 6.4 tarballs --- Makefile | 2 +- ghc-bootstrap.spec | 231 ++++++++++++++++++++++++++++++++++++ ghc-doc-no-ps-install.patch | 12 ++ needs.rebuild | 1 - sources | 5 +- 5 files changed, 248 insertions(+), 3 deletions(-) create mode 100644 ghc-bootstrap.spec create mode 100644 ghc-doc-no-ps-install.patch delete mode 100644 needs.rebuild diff --git a/Makefile b/Makefile index d85df4e..0709074 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,7 @@ # Makefile for source rpm: ghc # $Id$ NAME := ghc -SPECFILE = $(firstword $(wildcard *.spec)) +SPECFILE = ghc-bootstrap.spec define find-makefile-common for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done diff --git a/ghc-bootstrap.spec b/ghc-bootstrap.spec new file mode 100644 index 0000000..a5d6f1c --- /dev/null +++ b/ghc-bootstrap.spec @@ -0,0 +1,231 @@ +## ghc seeding bootstrap spec file + +%define ghcver ghc64 + +Name: ghc +Version: 6.4 +Release: 1%{?dist} +Summary: Glasgow Haskell Compilation system +License: BSD style +Group: Development/Languages +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-i386-unknown-linux.tar.bz2 +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-ppc-unknown-linux.tar.bz2 +Source3: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-x86_64-unknown-linux.tar.bz2 +URL: http://haskell.org/ghc/ +Requires: %{ghcver} = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +BuildRequires: sed +Prefix: %{_prefix} +Patch1: ghc-doc-no-ps-install.patch +ExclusiveArch: i386 ppc x86_64 + +%description +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interface. + +%package -n %{ghcver} +Summary: Documentation for GHC +Group: Development/Languages +Requires: gcc gmp-devel readline-devel + +%description -n %{ghcver} +GHC is a state-of-the-art programming suite for Haskell, a purely +functional programming language. It includes an optimising compiler +generating good code for a variety of platforms, together with an +interactive system for convenient, quick development. The +distribution includes space and time profiling facilities, a large +collection of libraries, and support for various language +extensions, including concurrency, exceptions, and a foreign language +interfaces. + +This package contains all the main files and libraries of version %{version}. + +%package -n %{ghcver}-prof +Summary: Profiling libraries for GHC +Group: Development/Libraries +Requires: %{ghcver} = %{version}-%{release} +Obsoletes: ghc-prof + +%description -n %{ghcver}-prof +Profiling libraries for Glorious Glasgow Haskell Compilation System +(GHC). They should be installed when GHC's profiling subsystem is +needed. + +%package doc +Summary: Documentation for GHC +Group: Development/Languages + +%description doc +Preformatted documentation for the Glorious Glasgow Haskell +Compilation System (GHC) and its libraries. It should be installed if +you like to have local access to the documentation in HTML format. + +# the debuginfo subpackage is currently empty anyway, so don't generate it +%define debug_package %{nil} +%define __spec_install_post /usr/lib/rpm/brp-compress + +%prep +rm -rf %{name}-%{version} +tar jxf ${RPM_SOURCE_DIR}/%{name}-%{version}-%{_arch}-unknown-linux.tar.bz2 +%setup -T -D +%patch1 -p1 -b .ps + +%build +./configure --prefix=%{_prefix} --libdir=%{_libdir} +make prefix=%{_prefix} libdir=%{_libdir}/%{name}-%{version} + +%install +rm -rf $RPM_BUILD_ROOT + +make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} datadir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} htmldir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} install-dirs install-bin install-libs install-datas install-docs + +SRC_TOP=$PWD +rm -f rpm-*-filelist rpm-*.files +( cd $RPM_BUILD_ROOT + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) +) + +# make paths absolute (filter "./usr" to "/usr") +sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files + +cat rpm-dir.files rpm-lib.files > rpm-base-filelist +cat rpm-dir.files rpm-prof.files > rpm-prof-filelist + +%clean +rm -rf $RPM_BUILD_ROOT + +%post +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} +fi + +%post -n %{ghcver} +## tweak prefix in drivers scripts if relocating +if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then + BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` + sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf +fi + +%files +%defattr(-,root,root,-) +%{_bindir}/* +%exclude %{_bindir}/ghc*%{version} + +%files -n %{ghcver} -f rpm-base-filelist +%defattr(-,root,root,-) +%doc ANNOUNCE LICENSE README +%{_bindir}/ghc*%{version} +%config(noreplace) %{_libdir}/ghc-%{version}/package.conf + +%files -n %{ghcver}-prof -f rpm-prof-filelist +%defattr(-,root,root,-) + +%files doc +%defattr(-,root,root,-) +%{_docdir}/%{name}-%{version} + +%changelog +* Tue May 31 2005 Jens Petersen +- initial seed bootstrap package for Fedora Extras for i386, ppc and x86_64 +- add %%dist to release + +* Thu May 12 2005 Jens Petersen +- add build_prof and build_doc switches for -doc and -prof subpackages + +* Wed May 11 2005 Jens Petersen +- make package relocatable (ghc#1084122) + - add post install scripts to replace prefix in driver scripts + +* Wed Mar 16 2005 Jens Petersen +- make ghc require ghcver of same ver-rel + +* Tue Mar 15 2005 Jens Petersen +- ghc requires ghcver (Amanda Clare) + +* Sat Mar 12 2005 Jens Petersen +- 6.4 release +- use sed instead of perl to tidy filelists +- no epoch for ghc64-prof's ghc64 requirement + +* Fri Jan 21 2005 Jens Petersen - 6.2.2-2 +- add x86_64 port + - build unregistered and without splitobjs + - specify libdir to configure and install +- rename ghc-prof to ghcXYZ-prof, which obsoletes ghc-prof + +* Mon Dec 6 2004 Jens Petersen - 6.2.2-1 +- move ghc requires to ghcXYZ + +* Wed Nov 24 2004 Jens Petersen - 6.2.2-0.fdr.1 +- ghc622 + - provide ghc = %%version +- require gcc, gmp-devel and readline-devel + +* Fri Oct 15 2004 Gerard Milmeister - 6.2.2-0.fdr.1 +- New Version 6.2.2 + +* Mon Mar 22 2004 Gerard Milmeister - 6.2.1-0.fdr.1 +- New Version 6.2.1 + +* Tue Dec 16 2003 Gerard Milmeister - 6.2-0.fdr.1 +- New Version 6.2 + +* Tue Dec 16 2003 Gerard Milmeister - 6.0.1-0.fdr.3 +- A few minor specfile tweaks + +* Mon Dec 15 2003 Gerard Milmeister - 6.0.1-0.fdr.2 +- Different file list generation + +* Mon Oct 20 2003 Gerard Milmeister - 6.0.1-0.fdr.1 +- First Fedora release +- Added generated html docs, so that haddock is not needed + +* Wed Sep 26 2001 Manuel Chakravarty +- small changes for 5.04 + +* Wed Sep 26 2001 Manuel Chakravarty +- split documentation off into a separate package +- adapt to new docbook setup in RH7.1 + +* Mon Apr 16 2001 Manuel Chakravarty +- revised for 5.00 +- also runs autoconf automagically if no ./configure found + +* Thu Jun 22 2000 Sven Panne +- removed explicit usage of hslibs/docs, it belongs to ghc/docs/set + +* Sun Apr 23 2000 Manuel Chakravarty +- revised for ghc 4.07; added suggestions from Pixel +- added profiling package + +* Tue Dec 7 1999 Manuel Chakravarty +- version for use from CVS + +* Thu Sep 16 1999 Manuel Chakravarty +- modified for GHC 4.04, patchlevel 1 (no more 62 tuple stuff); minimises use + of patch files - instead emits a build.mk on-the-fly + +* Sat Jul 31 1999 Manuel Chakravarty +- modified for GHC 4.04 + +* Wed Jun 30 1999 Manuel Chakravarty +- some more improvements from vbzoli + +* Fri Feb 26 1999 Manuel Chakravarty +- modified for GHC 4.02 + +* Thu Dec 24 1998 Zoltan Vorosbaranyi +- added BuildRoot +- files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib + +* Tue Jul 28 1998 Manuel Chakravarty +- original version diff --git a/ghc-doc-no-ps-install.patch b/ghc-doc-no-ps-install.patch new file mode 100644 index 0000000..e959aa1 --- /dev/null +++ b/ghc-doc-no-ps-install.patch @@ -0,0 +1,12 @@ +--- ghc-6.4/Makefile.in~ 2005-03-09 00:01:08.000000000 +0900 ++++ ghc-6.4/Makefile.in 2005-03-12 12:53:02.531724624 +0900 +@@ -274,9 +274,6 @@ + + install-docs : install-dirs-docs + if test -d share/html ; then $(CP) -r share/html/* $(htmldir) ; fi +- for i in share/*.ps; do \ +- $(CP) $$i $(psdir) ; \ +- done + + install-dirs-docs: + $(INSTALL_DIR) $(htmldir) diff --git a/needs.rebuild b/needs.rebuild deleted file mode 100644 index 815fd29..0000000 --- a/needs.rebuild +++ /dev/null @@ -1 +0,0 @@ -http://fedoraproject.org/wiki/Extras/Schedule/FC6MassRebuild diff --git a/sources b/sources index e83fb16..1fc3de8 100644 --- a/sources +++ b/sources @@ -1 +1,4 @@ -a394bf14e94c3bca5507d568fcc03375 ghc-6.4.2-src.tar.bz2 +45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 +89aaed2c09667f25a1777012a42200c7 ghc-6.4-i386-unknown-linux.tar.bz2 +6ad2f7df7f55e8cfec0504384bf664ea ghc-6.4-x86_64-unknown-linux.tar.bz2 +1400a1c158b07821f81ee5e4a7433b91 ghc-6.4-ppc-unknown-linux.tar.bz2 From f77d95821de74d0d148c5f6f5ebf0232cba7444a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 27 Sep 2006 12:34:59 +0000 Subject: [PATCH 019/530] revert temporary bootstrap to ghc-6.4.2 --- Makefile | 2 +- ghc-bootstrap.spec | 231 ------------------------------------ ghc-doc-no-ps-install.patch | 12 -- sources | 5 +- 4 files changed, 2 insertions(+), 248 deletions(-) delete mode 100644 ghc-bootstrap.spec delete mode 100644 ghc-doc-no-ps-install.patch diff --git a/Makefile b/Makefile index 0709074..d85df4e 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,7 @@ # Makefile for source rpm: ghc # $Id$ NAME := ghc -SPECFILE = ghc-bootstrap.spec +SPECFILE = $(firstword $(wildcard *.spec)) define find-makefile-common for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done diff --git a/ghc-bootstrap.spec b/ghc-bootstrap.spec deleted file mode 100644 index a5d6f1c..0000000 --- a/ghc-bootstrap.spec +++ /dev/null @@ -1,231 +0,0 @@ -## ghc seeding bootstrap spec file - -%define ghcver ghc64 - -Name: ghc -Version: 6.4 -Release: 1%{?dist} -Summary: Glasgow Haskell Compilation system -License: BSD style -Group: Development/Languages -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-i386-unknown-linux.tar.bz2 -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-ppc-unknown-linux.tar.bz2 -Source3: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-x86_64-unknown-linux.tar.bz2 -URL: http://haskell.org/ghc/ -Requires: %{ghcver} = %{version}-%{release} -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -BuildRequires: sed -Prefix: %{_prefix} -Patch1: ghc-doc-no-ps-install.patch -ExclusiveArch: i386 ppc x86_64 - -%description -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interface. - -%package -n %{ghcver} -Summary: Documentation for GHC -Group: Development/Languages -Requires: gcc gmp-devel readline-devel - -%description -n %{ghcver} -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interfaces. - -This package contains all the main files and libraries of version %{version}. - -%package -n %{ghcver}-prof -Summary: Profiling libraries for GHC -Group: Development/Libraries -Requires: %{ghcver} = %{version}-%{release} -Obsoletes: ghc-prof - -%description -n %{ghcver}-prof -Profiling libraries for Glorious Glasgow Haskell Compilation System -(GHC). They should be installed when GHC's profiling subsystem is -needed. - -%package doc -Summary: Documentation for GHC -Group: Development/Languages - -%description doc -Preformatted documentation for the Glorious Glasgow Haskell -Compilation System (GHC) and its libraries. It should be installed if -you like to have local access to the documentation in HTML format. - -# the debuginfo subpackage is currently empty anyway, so don't generate it -%define debug_package %{nil} -%define __spec_install_post /usr/lib/rpm/brp-compress - -%prep -rm -rf %{name}-%{version} -tar jxf ${RPM_SOURCE_DIR}/%{name}-%{version}-%{_arch}-unknown-linux.tar.bz2 -%setup -T -D -%patch1 -p1 -b .ps - -%build -./configure --prefix=%{_prefix} --libdir=%{_libdir} -make prefix=%{_prefix} libdir=%{_libdir}/%{name}-%{version} - -%install -rm -rf $RPM_BUILD_ROOT - -make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} datadir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} htmldir=$RPM_BUILD_ROOT%{_docdir}/%{name}-%{version} install-dirs install-bin install-libs install-datas install-docs - -SRC_TOP=$PWD -rm -f rpm-*-filelist rpm-*.files -( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) -) - -# make paths absolute (filter "./usr" to "/usr") -sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files - -cat rpm-dir.files rpm-lib.files > rpm-base-filelist -cat rpm-dir.files rpm-prof.files > rpm-prof-filelist - -%clean -rm -rf $RPM_BUILD_ROOT - -%post -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} -fi - -%post -n %{ghcver} -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf -fi - -%files -%defattr(-,root,root,-) -%{_bindir}/* -%exclude %{_bindir}/ghc*%{version} - -%files -n %{ghcver} -f rpm-base-filelist -%defattr(-,root,root,-) -%doc ANNOUNCE LICENSE README -%{_bindir}/ghc*%{version} -%config(noreplace) %{_libdir}/ghc-%{version}/package.conf - -%files -n %{ghcver}-prof -f rpm-prof-filelist -%defattr(-,root,root,-) - -%files doc -%defattr(-,root,root,-) -%{_docdir}/%{name}-%{version} - -%changelog -* Tue May 31 2005 Jens Petersen -- initial seed bootstrap package for Fedora Extras for i386, ppc and x86_64 -- add %%dist to release - -* Thu May 12 2005 Jens Petersen -- add build_prof and build_doc switches for -doc and -prof subpackages - -* Wed May 11 2005 Jens Petersen -- make package relocatable (ghc#1084122) - - add post install scripts to replace prefix in driver scripts - -* Wed Mar 16 2005 Jens Petersen -- make ghc require ghcver of same ver-rel - -* Tue Mar 15 2005 Jens Petersen -- ghc requires ghcver (Amanda Clare) - -* Sat Mar 12 2005 Jens Petersen -- 6.4 release -- use sed instead of perl to tidy filelists -- no epoch for ghc64-prof's ghc64 requirement - -* Fri Jan 21 2005 Jens Petersen - 6.2.2-2 -- add x86_64 port - - build unregistered and without splitobjs - - specify libdir to configure and install -- rename ghc-prof to ghcXYZ-prof, which obsoletes ghc-prof - -* Mon Dec 6 2004 Jens Petersen - 6.2.2-1 -- move ghc requires to ghcXYZ - -* Wed Nov 24 2004 Jens Petersen - 6.2.2-0.fdr.1 -- ghc622 - - provide ghc = %%version -- require gcc, gmp-devel and readline-devel - -* Fri Oct 15 2004 Gerard Milmeister - 6.2.2-0.fdr.1 -- New Version 6.2.2 - -* Mon Mar 22 2004 Gerard Milmeister - 6.2.1-0.fdr.1 -- New Version 6.2.1 - -* Tue Dec 16 2003 Gerard Milmeister - 6.2-0.fdr.1 -- New Version 6.2 - -* Tue Dec 16 2003 Gerard Milmeister - 6.0.1-0.fdr.3 -- A few minor specfile tweaks - -* Mon Dec 15 2003 Gerard Milmeister - 6.0.1-0.fdr.2 -- Different file list generation - -* Mon Oct 20 2003 Gerard Milmeister - 6.0.1-0.fdr.1 -- First Fedora release -- Added generated html docs, so that haddock is not needed - -* Wed Sep 26 2001 Manuel Chakravarty -- small changes for 5.04 - -* Wed Sep 26 2001 Manuel Chakravarty -- split documentation off into a separate package -- adapt to new docbook setup in RH7.1 - -* Mon Apr 16 2001 Manuel Chakravarty -- revised for 5.00 -- also runs autoconf automagically if no ./configure found - -* Thu Jun 22 2000 Sven Panne -- removed explicit usage of hslibs/docs, it belongs to ghc/docs/set - -* Sun Apr 23 2000 Manuel Chakravarty -- revised for ghc 4.07; added suggestions from Pixel -- added profiling package - -* Tue Dec 7 1999 Manuel Chakravarty -- version for use from CVS - -* Thu Sep 16 1999 Manuel Chakravarty -- modified for GHC 4.04, patchlevel 1 (no more 62 tuple stuff); minimises use - of patch files - instead emits a build.mk on-the-fly - -* Sat Jul 31 1999 Manuel Chakravarty -- modified for GHC 4.04 - -* Wed Jun 30 1999 Manuel Chakravarty -- some more improvements from vbzoli - -* Fri Feb 26 1999 Manuel Chakravarty -- modified for GHC 4.02 - -* Thu Dec 24 1998 Zoltan Vorosbaranyi -- added BuildRoot -- files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib - -* Tue Jul 28 1998 Manuel Chakravarty -- original version diff --git a/ghc-doc-no-ps-install.patch b/ghc-doc-no-ps-install.patch deleted file mode 100644 index e959aa1..0000000 --- a/ghc-doc-no-ps-install.patch +++ /dev/null @@ -1,12 +0,0 @@ ---- ghc-6.4/Makefile.in~ 2005-03-09 00:01:08.000000000 +0900 -+++ ghc-6.4/Makefile.in 2005-03-12 12:53:02.531724624 +0900 -@@ -274,9 +274,6 @@ - - install-docs : install-dirs-docs - if test -d share/html ; then $(CP) -r share/html/* $(htmldir) ; fi -- for i in share/*.ps; do \ -- $(CP) $$i $(psdir) ; \ -- done - - install-dirs-docs: - $(INSTALL_DIR) $(htmldir) diff --git a/sources b/sources index 1fc3de8..e83fb16 100644 --- a/sources +++ b/sources @@ -1,4 +1 @@ -45ea4e15f135698feb88d12c5000aaf8 ghc-6.4-src.tar.bz2 -89aaed2c09667f25a1777012a42200c7 ghc-6.4-i386-unknown-linux.tar.bz2 -6ad2f7df7f55e8cfec0504384bf664ea ghc-6.4-x86_64-unknown-linux.tar.bz2 -1400a1c158b07821f81ee5e4a7433b91 ghc-6.4-ppc-unknown-linux.tar.bz2 +a394bf14e94c3bca5507d568fcc03375 ghc-6.4.2-src.tar.bz2 From 4eb22b2025e6a0cb9fed1b4372a3edc364260f52 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 28 Sep 2006 01:44:23 +0000 Subject: [PATCH 020/530] turn on docs again --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index c166781..b38e836 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,11 +2,11 @@ # speed up test builds by not building profiled libraries %define build_prof 1 -%define build_doc 0 +%define build_doc 1 Name: ghc Version: 6.4.2 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -174,6 +174,9 @@ fi %changelog +* Thu Sep 28 2006 Jens Petersen - 6.4.2-4 +- turn on docs generation again + * Mon Sep 25 2006 Jens Petersen - 6.4.2-3.fc6 - ghost package.conf.old (Gérard Milmeister) - set unconfined_execmem_exec_t context on executables with ghc rts (#195821) From 812b06678617ab9d6faacb5954474b3f419b02f8 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 3 Nov 2006 05:00:12 +0000 Subject: [PATCH 021/530] - update to 6.6 release - buildrequire haddock >= 0.8 - fix summary of ghcver package (Michel Salim, #209574) --- .cvsignore | 3 ++- ghc.spec | 22 ++++++++++++++-------- sources | 3 ++- 3 files changed, 18 insertions(+), 10 deletions(-) diff --git a/.cvsignore b/.cvsignore index b512e86..fec0b68 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1,2 @@ -ghc-6.4.2-src.tar.bz2 +ghc-6.6-src.tar.bz2 +ghc-6.6-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index b38e836..ce2d5cf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,16 +1,17 @@ -%define ghcver ghc642 +%define ghcver ghc66 # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 1 Name: ghc -Version: 6.4.2 -Release: 4%{?dist} +Version: 6.6 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages -Source: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) @@ -20,7 +21,7 @@ Buildrequires: libX11-devel, libXt-devel Buildrequires: freeglut-devel, openal-devel %if %{build_doc} # haddock generates docs in libraries -Buildrequires: libxslt, docbook-style-xsl, haddock +Buildrequires: libxslt, docbook-style-xsl, haddock >= 0.8 %endif Prefix: %{_prefix} @@ -35,7 +36,7 @@ extensions, including concurrency, exceptions, and a foreign language interface. %package -n %{ghcver} -Summary: Documentation for GHC +Summary: Glasgow Haskell Compilation system Group: Development/Languages Requires: gcc gmp-devel readline-devel @@ -79,7 +80,7 @@ you like to have local access to the documentation in HTML format. %define __spec_install_post /usr/lib/rpm/brp-compress %prep -%setup -q -n ghc-%{version} +%setup -q -n ghc-%{version} -b1 %build %if !%{build_prof} @@ -154,7 +155,7 @@ fi %files -n %{ghcver} -f rpm-base-filelist %defattr(-,root,root,-) -%doc ghc/ANNOUNCE ghc/LICENSE ghc/README +%doc ANNOUNCE HACKING LICENSE README %{_bindir}/ghc*%{version} %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %ghost %{_libdir}/ghc-%{version}/package.conf.old @@ -174,6 +175,11 @@ fi %changelog +* Fri Nov 3 2006 Jens Petersen - 6.6-1 +- update to 6.6 release +- buildrequire haddock >= 0.8 +- fix summary of ghcver package (Michel Salim, #209574) + * Thu Sep 28 2006 Jens Petersen - 6.4.2-4 - turn on docs generation again diff --git a/sources b/sources index e83fb16..c2bf014 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ -a394bf14e94c3bca5507d568fcc03375 ghc-6.4.2-src.tar.bz2 +2427a8d7d14f86e0878df6b54938acf7 ghc-6.6-src.tar.bz2 +14b22fce36caffa509046361724bc119 ghc-6.6-src-extralibs.tar.bz2 From 2047747149546769d7f62c09bef928d9d038075f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 21 Jan 2007 22:42:51 +0000 Subject: [PATCH 022/530] - remove truncated duplicate Typeable.h header in network (Bryan O'Sullivan) Resolves: #222865 --- ghc.spec | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index ce2d5cf..433cd82 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,7 +6,7 @@ Name: ghc Version: 6.6 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -90,6 +90,9 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk ./configure --prefix=%{_prefix} --libdir=%{_libdir} +# drop truncated copy of header (#222865) +rm libraries/network/include/Typeable.h + make all %if %{build_doc} make html @@ -175,6 +178,10 @@ fi %changelog +* Mon Jan 22 2007 Jens Petersen - 6.6-2 +- remove truncated duplicate Typeable.h header in network package + (Bryan O'Sullivan, #222865) + * Fri Nov 3 2006 Jens Petersen - 6.6-1 - update to 6.6 release - buildrequire haddock >= 0.8 From 67f21357a4e8dbfa27ca3f9d3be93ada01292c92 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Thu, 10 May 2007 17:09:49 +0000 Subject: [PATCH 023/530] Update to GHC 6.6.1 --- .cvsignore | 4 ++-- ghc.spec | 9 ++++++--- sources | 4 ++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/.cvsignore b/.cvsignore index fec0b68..a10dfe3 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.6-src.tar.bz2 -ghc-6.6-src-extralibs.tar.bz2 +ghc-6.6.1-src.tar.bz2 +ghc-6.6.1-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 433cd82..7ff0172 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,12 @@ -%define ghcver ghc66 +%define ghcver ghc661 # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 1 Name: ghc -Version: 6.6 -Release: 2%{?dist} +Version: 6.6.1 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system License: BSD style Group: Development/Languages @@ -178,6 +178,9 @@ fi %changelog +* Wed May 9 2007 Bryan O'Sullivan - 6.6.1-1 +- update to 6.6.1 release + * Mon Jan 22 2007 Jens Petersen - 6.6-2 - remove truncated duplicate Typeable.h header in network package (Bryan O'Sullivan, #222865) diff --git a/sources b/sources index c2bf014..58ca312 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -2427a8d7d14f86e0878df6b54938acf7 ghc-6.6-src.tar.bz2 -14b22fce36caffa509046361724bc119 ghc-6.6-src-extralibs.tar.bz2 +dea271503463bd28c27f25ab90998633 ghc-6.6.1-src.tar.bz2 +43a26b81608b206c056adc3032f7da2a ghc-6.6.1-src-extralibs.tar.bz2 From 19c596ba3c71812d14011b7b3b4ecb66b19a5652 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Thu, 10 May 2007 17:53:17 +0000 Subject: [PATCH 024/530] Exclude ppc64 for now (bug 239713) --- ghc.spec | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 7ff0172..253204a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,8 +6,10 @@ Name: ghc Version: 6.6.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system +# See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 +ExcludeArch: ppc64 License: BSD style Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -178,6 +180,9 @@ fi %changelog +* Thu May 10 2007 Bryan O'Sullivan - 6.6.1-2 +- exclude ppc64 for now, due to lack of time to bootstrap + * Wed May 9 2007 Bryan O'Sullivan - 6.6.1-1 - update to 6.6.1 release From 5ae9c5759dda15cecca9302bd50c22f1c3a54006 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Thu, 10 May 2007 19:52:43 +0000 Subject: [PATCH 025/530] Install new man page for GHC --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 253204a..df1c584 100644 --- a/ghc.spec +++ b/ghc.spec @@ -6,7 +6,7 @@ Name: ghc Version: 6.6.1 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: ppc64 @@ -106,7 +106,7 @@ rm -rf $RPM_BUILD_ROOT make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} install %if %{build_doc} -make datadir=$RPM_BUILD_ROOT%{_docdir}/ghc-%{version} XMLDocWays="html" install-docs +make mandir=$RPM_BUILD_ROOT%{_mandir} datadir=$RPM_BUILD_ROOT%{_docdir}/ghc-%{version} XMLDocWays="html" install-docs %endif SRC_TOP=$PWD @@ -156,6 +156,7 @@ fi %defattr(-,root,root,-) %{_bindir}/* %exclude %{_bindir}/ghc*%{version} +%doc %{_mandir}/man1/ghc.* %files -n %{ghcver} -f rpm-base-filelist @@ -180,6 +181,9 @@ fi %changelog +* Thu May 10 2007 Bryan O'Sullivan - 6.6.1-3 +- install man page for ghc + * Thu May 10 2007 Bryan O'Sullivan - 6.6.1-2 - exclude ppc64 for now, due to lack of time to bootstrap From cdb710ffe5a1c9f016ad869ead3654cb222db6d7 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Sun, 30 Sep 2007 03:06:57 +0000 Subject: [PATCH 026/530] Update to ghc-6.8.0.20070928 --- .cvsignore | 4 +-- ghc.spec | 85 +++++++++++++++++++++++++++++++++++++++++++++--------- sources | 4 +-- 3 files changed, 75 insertions(+), 18 deletions(-) diff --git a/.cvsignore b/.cvsignore index a10dfe3..7758321 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.6.1-src.tar.bz2 -ghc-6.6.1-src-extralibs.tar.bz2 +ghc-6.8.0.20070928-src-extralibs.tar.bz2 +ghc-6.8.0.20070928-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index df1c584..7c6071b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,24 @@ -%define ghcver ghc661 +%define ghcver ghc680 # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 1 +# Fixing packaging problems can be a tremendous pain because it +# generally requires a complete rebuild, which takes hours. To offset +# the misery, do a complete build once using "rpmbuild -bc", then copy +# your built tree to a directory of the same name suffixed with +# ".built", using "cp -al". Finally, set this variable, and it will +# copy the already-built tree into place during %build instead of +# actually doing the build. +# +# Obviously, this can only work if you leave the %build section +# completely untouched between builds. +%define package_debugging 0 + Name: ghc -Version: 6.6.1 -Release: 3%{?dist} +Version: 6.8.0.20070928 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: ppc64 @@ -15,15 +27,15 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 URL: http://haskell.org/ghc/ -Requires: %{ghcver} = %{version}-%{release} +Requires: %{ghcver} = %{version}-%{release}, chkconfig BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) BuildRequires: ghc, sed -Buildrequires: gmp-devel, readline-devel -Buildrequires: libX11-devel, libXt-devel -Buildrequires: freeglut-devel, openal-devel +BuildRequires: gmp-devel, readline-devel +BuildRequires: libX11-devel, libXt-devel +BuildRequires: freeglut-devel, openal-devel %if %{build_doc} # haddock generates docs in libraries -Buildrequires: libxslt, docbook-style-xsl, haddock >= 0.8 +BuildRequires: libxslt, docbook-style-xsl, haddock >= 0.8 %endif Prefix: %{_prefix} @@ -82,31 +94,49 @@ you like to have local access to the documentation in HTML format. %define __spec_install_post /usr/lib/rpm/brp-compress %prep -%setup -q -n ghc-%{version} -b1 +%setup -q -n %{name}-%{version} -b1 %build +%if %{package_debugging} +cd .. +rm -rf %{name}-%{version} +cp -al %{name}-%{version}.built %{name}-%{version} +cd %{name}-%{version} +exit 0 +%endif + %if !%{build_prof} echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif -./configure --prefix=%{_prefix} --libdir=%{_libdir} +./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ + --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ + --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ + --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} # drop truncated copy of header (#222865) rm libraries/network/include/Typeable.h -make all +make %{_smp_mflags} docdir=%{_docdir}/%{name}-%{version} all %if %{build_doc} -make html +make %{_smp_mflags} docdir=%{_docdir}/%{name}-%{version} html +make %{_smp_mflags} -C libraries HADDOCK_DOCS=YES +( cd libraries/Cabal && docbook2html doc/Cabal.xml --output doc/Cabal ) %endif %install rm -rf $RPM_BUILD_ROOT -make prefix=$RPM_BUILD_ROOT%{_prefix} libdir=$RPM_BUILD_ROOT%{_libdir}/%{name}-%{version} install +make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} install %if %{build_doc} -make mandir=$RPM_BUILD_ROOT%{_mandir} datadir=$RPM_BUILD_ROOT%{_docdir}/ghc-%{version} XMLDocWays="html" install-docs +make DESTDIR=${RPM_BUILD_ROOT} docdir=%{_docdir}/%{name}-%{version} \ + XMLDocWays="html" HADDOCK_DOCS=YES install-docs +mv ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries \ + ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version} +cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries %endif SRC_TOP=$PWD @@ -126,6 +156,7 @@ cat rpm-dir.files rpm-prof.files > rpm-prof-filelist # create package.conf.old touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old +mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs-ghc %clean rm -rf $RPM_BUILD_ROOT @@ -140,6 +171,22 @@ fi /usr/bin/chcon -t unconfined_execmem_exec_t %{_bindir}/{hasktags,runghc,runhaskell} >/dev/null 2>&1 || : +# Alas, GHC, Hugs, and nhc all come with different set of tools in +# addition to a runFOO: +# +# * GHC: hsc2hs +# * Hugs: hsc2hs, cpphs +# * nhc: cpphs +# +# Therefore it is currently not possible to use --slave below to form +# link groups under a single name 'runhaskell'. Either these tools +# should be disentangled from the Haskell implementations, or all +# implementations should have the same set of tools. *sigh* + +update-alternatives --install %{_bindir}/runhaskell runhaskell \ + %{_bindir}/runghc 500 +update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ + %{_bindir}/hsc2hs-ghc 500 %post -n %{ghcver} ## tweak prefix in drivers scripts if relocating @@ -152,6 +199,13 @@ fi /usr/bin/chcon -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/{ghc-%{version},ghc-pkg.bin,hsc2hs-bin} >/dev/null 2>&1 || : +%preun +if test "$1" = 0; then + update-alternatives --remove runhaskell %{_bindir}/runghc + update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc +fi + + %files %defattr(-,root,root,-) %{_bindir}/* @@ -181,6 +235,9 @@ fi %changelog +* Sat Sep 29 2007 Bryan O'Sullivan - 6.8.0.20070928-1 +- prepare for GHC 6.8.1 by building a release candidate snapshot + * Thu May 10 2007 Bryan O'Sullivan - 6.6.1-3 - install man page for ghc diff --git a/sources b/sources index 58ca312..0824dd8 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -dea271503463bd28c27f25ab90998633 ghc-6.6.1-src.tar.bz2 -43a26b81608b206c056adc3032f7da2a ghc-6.6.1-src-extralibs.tar.bz2 +8699ec00c510077ad6c632aea19ec1e0 ghc-6.8.0.20070928-src-extralibs.tar.bz2 +2f3d20ad0c68cd77a06b708e4d8360c5 ghc-6.8.0.20070928-src.tar.bz2 From 11b87bfd1351842af40d900f7479fa7fe081a6c5 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Sun, 30 Sep 2007 03:18:21 +0000 Subject: [PATCH 027/530] Work around rpm braindamage: you can't have "%" in comments!? --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7c6071b..9c684bf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,10 +9,10 @@ # the misery, do a complete build once using "rpmbuild -bc", then copy # your built tree to a directory of the same name suffixed with # ".built", using "cp -al". Finally, set this variable, and it will -# copy the already-built tree into place during %build instead of +# copy the already-built tree into place during build instead of # actually doing the build. # -# Obviously, this can only work if you leave the %build section +# Obviously, this can only work if you leave the build section # completely untouched between builds. %define package_debugging 0 From a20a5e59473b87e8f183642ee145d7cb377019fc Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Sun, 30 Sep 2007 03:53:49 +0000 Subject: [PATCH 028/530] Add happy to buldreqs --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9c684bf..f1fe05d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.0.20070928 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: ppc64 @@ -29,7 +29,7 @@ Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release}, chkconfig BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -BuildRequires: ghc, sed +BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, readline-devel BuildRequires: libX11-devel, libXt-devel BuildRequires: freeglut-devel, openal-devel @@ -235,6 +235,9 @@ fi %changelog +* Sat Sep 29 2007 Bryan O'Sullivan - 6.8.0.20070928-2 +- add happy to BuildRequires + * Sat Sep 29 2007 Bryan O'Sullivan - 6.8.0.20070928-1 - prepare for GHC 6.8.1 by building a release candidate snapshot From e8ba9bc72a5d02a0c0000dd3ae787005a25539d4 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Tue, 6 Nov 2007 00:35:13 +0000 Subject: [PATCH 029/530] Upgrade to ghc 6.8.1 --- .cvsignore | 4 ++-- ghc.spec | 14 ++++++++------ sources | 4 ++-- 3 files changed, 12 insertions(+), 10 deletions(-) diff --git a/.cvsignore b/.cvsignore index 7758321..ba42edc 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.8.0.20070928-src-extralibs.tar.bz2 -ghc-6.8.0.20070928-src.tar.bz2 +ghc-6.8.1-src-extralibs.tar.bz2 +ghc-6.8.1-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index f1fe05d..717fbfa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,4 @@ -%define ghcver ghc680 +%define ghcver ghc681 # speed up test builds by not building profiled libraries %define build_prof 1 @@ -17,12 +17,12 @@ %define package_debugging 0 Name: ghc -Version: 6.8.0.20070928 -Release: 2%{?dist} +Version: 6.8.1 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: ppc64 -License: BSD style +License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 @@ -37,7 +37,6 @@ BuildRequires: freeglut-devel, openal-devel # haddock generates docs in libraries BuildRequires: libxslt, docbook-style-xsl, haddock >= 0.8 %endif -Prefix: %{_prefix} %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -82,7 +81,7 @@ needed. %package doc Summary: Documentation for GHC Group: Development/Languages -Requires: %{name} +Requires: %{name} = %{version}-%{release} %description doc Preformatted documentation for the Glorious Glasgow Haskell @@ -235,6 +234,9 @@ fi %changelog +* Sun Nov 4 2007 Michel Salim - 6.8.1-1 +- Update to 6.8.1 + * Sat Sep 29 2007 Bryan O'Sullivan - 6.8.0.20070928-2 - add happy to BuildRequires diff --git a/sources b/sources index 0824dd8..921acc4 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -8699ec00c510077ad6c632aea19ec1e0 ghc-6.8.0.20070928-src-extralibs.tar.bz2 -2f3d20ad0c68cd77a06b708e4d8360c5 ghc-6.8.0.20070928-src.tar.bz2 +f91de87e7c0a3fe2f27c5a83212d9743 ghc-6.8.1-src-extralibs.tar.bz2 +8d47d4dcde96c31fe8bedcee7f99eaf1 ghc-6.8.1-src.tar.bz2 From 8e74151e8191fa32a76b77d0f47aaa52fc528d25 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 23 Nov 2007 18:15:15 +0000 Subject: [PATCH 030/530] Exclude alpha --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 717fbfa..b771ba6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,10 +18,10 @@ Name: ghc Version: 6.8.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 -ExcludeArch: ppc64 +ExcludeArch: alpha ppc64 License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -234,6 +234,9 @@ fi %changelog +* Fri Nov 23 2007 Bryan O'Sullivan - 6.8.1-2 +- Exclude alpha + * Sun Nov 4 2007 Michel Salim - 6.8.1-1 - Update to 6.8.1 From 7528b142b9142f6642c4bf53ec31a9b6b5e0320a Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 12 Dec 2007 22:36:10 +0000 Subject: [PATCH 031/530] ghc 6.8.2 --- .cvsignore | 4 ++-- ghc.spec | 9 ++++++--- sources | 4 ++-- 3 files changed, 10 insertions(+), 7 deletions(-) diff --git a/.cvsignore b/.cvsignore index ba42edc..89f9e8f 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.8.1-src-extralibs.tar.bz2 -ghc-6.8.1-src.tar.bz2 +ghc-6.8.2-src.tar.bz2 +ghc-6.8.2-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index b771ba6..bbac0e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,4 @@ -%define ghcver ghc681 +%define ghcver ghc682 # speed up test builds by not building profiled libraries %define build_prof 1 @@ -17,8 +17,8 @@ %define package_debugging 0 Name: ghc -Version: 6.8.1 -Release: 2%{?dist} +Version: 6.8.2 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -234,6 +234,9 @@ fi %changelog +* Tue Dec 12 2007 Bryan O'Sullivan - 6.8.2-1 +- Update to 6.8.2 + * Fri Nov 23 2007 Bryan O'Sullivan - 6.8.1-2 - Exclude alpha diff --git a/sources b/sources index 921acc4..f543d6d 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -f91de87e7c0a3fe2f27c5a83212d9743 ghc-6.8.1-src-extralibs.tar.bz2 -8d47d4dcde96c31fe8bedcee7f99eaf1 ghc-6.8.1-src.tar.bz2 +43108417594be7eba0918c459e871e40 ghc-6.8.2-src.tar.bz2 +d199c50814188fb77355d41058b8613c ghc-6.8.2-src-extralibs.tar.bz2 From 7728a76fc593152571ac25ff99fa6a71591435be Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 12 Dec 2007 23:21:18 +0000 Subject: [PATCH 032/530] Import some changes from F-8 tree --- ghc.spec | 15 +-------------- 1 file changed, 1 insertion(+), 14 deletions(-) diff --git a/ghc.spec b/ghc.spec index bbac0e2..02170aa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -162,12 +162,6 @@ rm -rf $RPM_BUILD_ROOT %post -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/{ghcprof,hsc2hs} -fi - /usr/bin/chcon -t unconfined_execmem_exec_t %{_bindir}/{hasktags,runghc,runhaskell} >/dev/null 2>&1 || : # Alas, GHC, Hugs, and nhc all come with different set of tools in @@ -188,13 +182,6 @@ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 %post -n %{ghcver} -## tweak prefix in drivers scripts if relocating -if [ "${RPM_INSTALL_PREFIX}" != "%{_prefix}" ]; then - BINDIR=`echo %{_bindir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - LIBDIR=`echo %{_libdir} | sed -e "s|%{_prefix}|${RPM_INSTALL_PREFIX}|"` - sed -i "s|%{_prefix}|${RPM_INSTALL_PREFIX}|" ${BINDIR}/ghc*-%{version} ${LIBDIR}/ghc-%{version}/package.conf -fi - /usr/bin/chcon -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/{ghc-%{version},ghc-pkg.bin,hsc2hs-bin} >/dev/null 2>&1 || : From d59db7372a1e5ffeb82437a34a3e56c039d2e7ba Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 7 Jan 2008 22:57:23 +0000 Subject: [PATCH 033/530] Fix haddock paths --- ghc.spec | 29 +++++++++++++++++++++-------- 1 file changed, 21 insertions(+), 8 deletions(-) diff --git a/ghc.spec b/ghc.spec index 02170aa..8301aeb 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -113,14 +113,24 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ + --docdir=%{_docdir}/%{name}-%{version} \ + --htmldir=%{_docdir}/%{name}-%{version} + +cat <<'HADDOCK_PATH_HACK' >> mk/build.mk +docdir := %{_docdir}/%{name}-%{version} +htmldir := $(docdir) +dvidir := $(docdir) +pdfdir := $(docdir) +psdir := $(docdir) +HADDOCK_PATH_HACK # drop truncated copy of header (#222865) rm libraries/network/include/Typeable.h -make %{_smp_mflags} docdir=%{_docdir}/%{name}-%{version} all +make %{_smp_mflags} all %if %{build_doc} -make %{_smp_mflags} docdir=%{_docdir}/%{name}-%{version} html +make %{_smp_mflags} html make %{_smp_mflags} -C libraries HADDOCK_DOCS=YES ( cd libraries/Cabal && docbook2html doc/Cabal.xml --output doc/Cabal ) %endif @@ -131,10 +141,7 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} install %if %{build_doc} -make DESTDIR=${RPM_BUILD_ROOT} docdir=%{_docdir}/%{name}-%{version} \ - XMLDocWays="html" HADDOCK_DOCS=YES install-docs -mv ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries \ - ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version} +make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries %endif @@ -221,12 +228,18 @@ fi %changelog +* Mon Jan 07 2008 Bryan O'Sullivan - 6.8.2-3 +- Fix haddock installation paths + * Tue Dec 12 2007 Bryan O'Sullivan - 6.8.2-1 - Update to 6.8.2 * Fri Nov 23 2007 Bryan O'Sullivan - 6.8.1-2 - Exclude alpha +* Thu Nov 8 2007 Bryan O'Sullivan - 6.8.1-2 +- Drop bit-rotted attempts at making package relocatable + * Sun Nov 4 2007 Michel Salim - 6.8.1-1 - Update to 6.8.1 From f57118ecb9bb7e9e0e4412bed531f4f3916f35d3 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 7 Jan 2008 23:24:04 +0000 Subject: [PATCH 034/530] Old configure does not grok docdir,htmldir --- ghc.spec | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 8301aeb..3d8d27c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -113,9 +113,7 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --docdir=%{_docdir}/%{name}-%{version} \ - --htmldir=%{_docdir}/%{name}-%{version} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} cat <<'HADDOCK_PATH_HACK' >> mk/build.mk docdir := %{_docdir}/%{name}-%{version} From 3d1944144ef34d1eebffa900929e41d2f2af1e52 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Tue, 22 Jan 2008 01:10:50 +0000 Subject: [PATCH 035/530] Sync up with fixes from F-8 --- ghc.spec | 19 ++++++++++++++----- 1 file changed, 14 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3d8d27c..9a44a65 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 4%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -113,9 +113,11 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ + --docdir=%{_docdir}/%{name}-%{version} \ + --htmldir=%{_docdir}/%{name}-%{version} -cat <<'HADDOCK_PATH_HACK' >> mk/build.mk +cat <> mk/build.mk docdir := %{_docdir}/%{name}-%{version} htmldir := $(docdir) dvidir := $(docdir) @@ -140,6 +142,10 @@ make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} install %if %{build_doc} make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs +if [ -d ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries ]; then + mv ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries \ + ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version} +fi cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries %endif @@ -226,8 +232,11 @@ fi %changelog -* Mon Jan 07 2008 Bryan O'Sullivan - 6.8.2-3 -- Fix haddock installation paths +* Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-7 +- More attempts to fix docdir + +* Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-6 +- Fix docdir * Tue Dec 12 2007 Bryan O'Sullivan - 6.8.2-1 - Update to 6.8.2 From 0a7ad4bf3683dfa0537542349c3f94bfce159ee0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 14 Feb 2008 07:36:23 +0000 Subject: [PATCH 036/530] rebuild with gcc43 --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 9a44a65..673d0b3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -232,6 +232,9 @@ fi %changelog +* Thu Feb 14 2008 Jens Petersen - 6.8.2-9 +- rebuild with gcc43 + * Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-7 - More attempts to fix docdir From 1892b30c0b5916adf5a26102c60122c150dab48a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 14 Feb 2008 08:11:43 +0000 Subject: [PATCH 037/530] remove unrecognized --docdir from configure --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 673d0b3..053fd35 100644 --- a/ghc.spec +++ b/ghc.spec @@ -114,7 +114,6 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --docdir=%{_docdir}/%{name}-%{version} \ --htmldir=%{_docdir}/%{name}-%{version} cat <> mk/build.mk @@ -233,6 +232,7 @@ fi %changelog * Thu Feb 14 2008 Jens Petersen - 6.8.2-9 +- remove unrecognized --docdir from configure - rebuild with gcc43 * Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-7 From bae7070ccb678e5c5ca2cd702db70b5237afafcb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 14 Feb 2008 08:31:32 +0000 Subject: [PATCH 038/530] - remove unrecognized --htmldir from configure - drop old buildrequires on libX11-devel and libXt-devel --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 053fd35..7487d70 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,8 @@ Requires: %{ghcver} = %{version}-%{release}, chkconfig BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, readline-devel -BuildRequires: libX11-devel, libXt-devel +# X11 is no longer in ghc extralibs +#BuildRequires: libX11-devel, libXt-devel BuildRequires: freeglut-devel, openal-devel %if %{build_doc} # haddock generates docs in libraries @@ -113,8 +114,7 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --htmldir=%{_docdir}/%{name}-%{version} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} cat <> mk/build.mk docdir := %{_docdir}/%{name}-%{version} @@ -232,7 +232,8 @@ fi %changelog * Thu Feb 14 2008 Jens Petersen - 6.8.2-9 -- remove unrecognized --docdir from configure +- remove unrecognized --docdir and --htmldir from configure +- drop old buildrequires on libX11-devel and libXt-devel - rebuild with gcc43 * Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-7 From ffb1ceca091939cd52deb58515c6b6049c558797 Mon Sep 17 00:00:00 2001 From: Jesse Keating Date: Mon, 18 Feb 2008 21:23:56 +0000 Subject: [PATCH 039/530] - Autorebuild for GCC 4.3 --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 7487d70..6a69436 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,7 +18,7 @@ Name: ghc Version: 6.8.2 -Release: 9%{?dist} +Release: 10%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -231,6 +231,9 @@ fi %changelog +* Mon Feb 18 2008 Fedora Release Engineering - 6.8.2-10 +- Autorebuild for GCC 4.3 + * Thu Feb 14 2008 Jens Petersen - 6.8.2-9 - remove unrecognized --docdir and --htmldir from configure - drop old buildrequires on libX11-devel and libXt-devel From f7ca4dbacba10b34caa71fb6c20473207ed2785a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 8 Apr 2008 06:46:15 +0000 Subject: [PATCH 040/530] bump changelog for another rebuidl attempt --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6a69436..b1a514f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -231,8 +231,8 @@ fi %changelog -* Mon Feb 18 2008 Fedora Release Engineering - 6.8.2-10 -- Autorebuild for GCC 4.3 +* Tue Apr 8 2008 Jens Petersen - 6.8.2-10 +- another rebuild attempt * Thu Feb 14 2008 Jens Petersen - 6.8.2-9 - remove unrecognized --docdir and --htmldir from configure From 548ce8bbda183d996513586389fa14c9938e0bb6 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 28 May 2008 18:25:23 +0000 Subject: [PATCH 041/530] GHC 6.8.3 release candidate. --- .cvsignore | 4 ++-- sources | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/.cvsignore b/.cvsignore index 89f9e8f..c789583 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.8.2-src.tar.bz2 -ghc-6.8.2-src-extralibs.tar.bz2 +ghc-6.8.2.20080527-src-extralibs.tar.bz2 +ghc-6.8.2.20080527-src.tar.bz2 diff --git a/sources b/sources index f543d6d..4db841c 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -43108417594be7eba0918c459e871e40 ghc-6.8.2-src.tar.bz2 -d199c50814188fb77355d41058b8613c ghc-6.8.2-src-extralibs.tar.bz2 +5b4fd263f4ae3c16ee97c5587f0f108e ghc-6.8.2.20080527-src-extralibs.tar.bz2 +fc57e6e290d0d6531a5e081b164fed78 ghc-6.8.2.20080527-src.tar.bz2 From 92410e9528ac47ac6571eb70e676b0025b5caccc Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 18 Jun 2008 16:44:34 +0000 Subject: [PATCH 042/530] First cut at ghc 6.8.3 spec file --- .cvsignore | 4 ++-- ghc-6.8.3-libraries-config.patch | 12 ++++++++++ ghc.spec | 40 +++++++++++++++----------------- sources | 4 ++-- 4 files changed, 35 insertions(+), 25 deletions(-) create mode 100644 ghc-6.8.3-libraries-config.patch diff --git a/.cvsignore b/.cvsignore index c789583..245433c 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.8.2.20080527-src-extralibs.tar.bz2 -ghc-6.8.2.20080527-src.tar.bz2 +ghc-6.8.3-src-extralibs.tar.bz2 +ghc-6.8.3-src.tar.bz2 diff --git a/ghc-6.8.3-libraries-config.patch b/ghc-6.8.3-libraries-config.patch new file mode 100644 index 0000000..f9e395a --- /dev/null +++ b/ghc-6.8.3-libraries-config.patch @@ -0,0 +1,12 @@ +--- ghc-6.8.3/libraries/Makefile~ 2008-06-17 23:10:28.000000000 -0700 ++++ ghc-6.8.3/libraries/Makefile 2008-06-17 23:21:21.000000000 -0700 +@@ -256,6 +256,9 @@ + --with-hc-pkg=../../utils/ghc-pkg/ghc-pkg-inplace \ + --with-hsc2hs=../../utils/hsc2hs/hsc2hs-inplace \ + --with-ld=$(LD) \ ++ --with-alex=$(ALEX) \ ++ --with-haddock=$(HADDOCK) \ ++ --with-happy=$(HAPPY) \ + --haddock-options="--use-contents=../index.html \ + --use-index=../doc-index.html" \ + $(FLAGGED_CONFIGURE_ARGS) \ diff --git a/ghc.spec b/ghc.spec index b1a514f..71fb15f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,4 @@ -%define ghcver ghc682 +%define ghcver ghc683 # speed up test builds by not building profiled libraries %define build_prof 1 @@ -17,15 +17,16 @@ %define package_debugging 0 Name: ghc -Version: 6.8.2 -Release: 10%{?dist} +Version: 6.8.3 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 License: BSD Group: Development/Languages -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 +Source0: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src.tar.bz2 +Source1: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src-extralibs.tar.bz2 +Patch0: ghc-6.8.3-libraries-config.patch URL: http://haskell.org/ghc/ Requires: %{ghcver} = %{version}-%{release}, chkconfig BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) @@ -35,8 +36,8 @@ BuildRequires: gmp-devel, readline-devel #BuildRequires: libX11-devel, libXt-devel BuildRequires: freeglut-devel, openal-devel %if %{build_doc} -# haddock generates docs in libraries -BuildRequires: libxslt, docbook-style-xsl, haddock >= 0.8 +# haddock generates docs in libraries, but haddock 2.0 is not compatible +BuildRequires: libxslt, docbook-style-xsl, haddock09 %endif %description @@ -96,6 +97,8 @@ you like to have local access to the documentation in HTML format. %prep %setup -q -n %{name}-%{version} -b1 +%patch0 -p1 -b .hdkl + %build %if %{package_debugging} cd .. @@ -110,6 +113,7 @@ echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif +HaddockCmd=%{_bindir}/haddock-0.9 \ ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -118,16 +122,16 @@ echo "GhcRTSWays=thr debug" >> mk/build.mk cat <> mk/build.mk docdir := %{_docdir}/%{name}-%{version} -htmldir := $(docdir) -dvidir := $(docdir) -pdfdir := $(docdir) -psdir := $(docdir) +htmldir := \$(docdir) +dvidir := \$(docdir) +pdfdir := \$(docdir) +psdir := \$(docdir) HADDOCK_PATH_HACK # drop truncated copy of header (#222865) rm libraries/network/include/Typeable.h -make %{_smp_mflags} all +make %{_smp_mflags} all libexecdir=%{_libexecdir} %if %{build_doc} make %{_smp_mflags} html make %{_smp_mflags} -C libraries HADDOCK_DOCS=YES @@ -137,7 +141,8 @@ make %{_smp_mflags} -C libraries HADDOCK_DOCS=YES %install rm -rf $RPM_BUILD_ROOT -make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} install +make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} \ + libexecdir=%{_libexecdir}/%{name}-%{version} install %if %{build_doc} make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs @@ -151,7 +156,7 @@ cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) + find .%{_libdir}/%{name}-%{version} .%{_libexecdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) ) # make paths absolute (filter "./usr" to "/usr") @@ -170,10 +175,7 @@ mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs-ghc %clean rm -rf $RPM_BUILD_ROOT - %post -/usr/bin/chcon -t unconfined_execmem_exec_t %{_bindir}/{hasktags,runghc,runhaskell} >/dev/null 2>&1 || : - # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: # @@ -191,10 +193,6 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 -%post -n %{ghcver} -/usr/bin/chcon -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/{ghc-%{version},ghc-pkg.bin,hsc2hs-bin} >/dev/null 2>&1 || : - - %preun if test "$1" = 0; then update-alternatives --remove runhaskell %{_bindir}/runghc diff --git a/sources b/sources index 4db841c..cf8f101 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -5b4fd263f4ae3c16ee97c5587f0f108e ghc-6.8.2.20080527-src-extralibs.tar.bz2 -fc57e6e290d0d6531a5e081b164fed78 ghc-6.8.2.20080527-src.tar.bz2 +5ac72f5d5433151cf6b718dc6601dc41 ghc-6.8.3-src-extralibs.tar.bz2 +dfa31028b4d06d1d226f55fe3a2ab7b3 ghc-6.8.3-src.tar.bz2 From fb0f222aeb9f5e2bca197da8442e1939094a6bc7 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 18 Jun 2008 19:49:45 +0000 Subject: [PATCH 043/530] GHC 6.8.3 --- ghc.spec | 53 +++++++++++++++++++---------------------------------- 1 file changed, 19 insertions(+), 34 deletions(-) diff --git a/ghc.spec b/ghc.spec index 71fb15f..6fc0ca5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,3 @@ -%define ghcver ghc683 - # speed up test builds by not building profiled libraries %define build_prof 1 %define build_doc 1 @@ -28,8 +26,9 @@ Source0: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src-extralibs.tar.bz2 Patch0: ghc-6.8.3-libraries-config.patch URL: http://haskell.org/ghc/ -Requires: %{ghcver} = %{version}-%{release}, chkconfig +Requires: chkconfig, gcc, gmp-devel, readline-devel BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +Obsoletes: ghc682, ghc681, ghc661, ghc66 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, readline-devel # X11 is no longer in ghc extralibs @@ -50,31 +49,14 @@ collection of libraries, and support for various language extensions, including concurrency, exceptions, and a foreign language interface. -%package -n %{ghcver} -Summary: Glasgow Haskell Compilation system -Group: Development/Languages -Requires: gcc gmp-devel readline-devel - -%description -n %{ghcver} -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interfaces. - -This package contains all the main files and libraries of version %{version}. - %if %{build_prof} -%package -n %{ghcver}-prof +%package prof Summary: Profiling libraries for GHC Group: Development/Libraries -Requires: %{ghcver} = %{version}-%{release} -Obsoletes: ghc-prof +Requires: %{name} = %{version}-%{release} +Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof -%description -n %{ghcver}-prof +%description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). They should be installed when GHC's profiling subsystem is needed. @@ -144,6 +126,10 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} \ libexecdir=%{_libexecdir}/%{name}-%{version} install +pushd ${RPM_BUILD_ROOT}/%{_libexecdir}/%{name}-%{version} +strip cgprof ghc-%{version} ghc-pkg.bin hsc2hs-bin unlit +popd + %if %{build_doc} make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs if [ -d ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries ]; then @@ -200,23 +186,17 @@ if test "$1" = 0; then fi -%files -%defattr(-,root,root,-) -%{_bindir}/* -%exclude %{_bindir}/ghc*%{version} -%doc %{_mandir}/man1/ghc.* - - -%files -n %{ghcver} -f rpm-base-filelist +%files -f rpm-base-filelist %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README -%{_bindir}/ghc*%{version} +%doc %{_mandir}/man1/ghc.* +%{_bindir}/* %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %ghost %{_libdir}/ghc-%{version}/package.conf.old %if %{build_prof} -%files -n %{ghcver}-prof -f rpm-prof-filelist +%files prof -f rpm-prof-filelist %defattr(-,root,root,-) %endif @@ -229,6 +209,11 @@ fi %changelog +* Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-1 +- Upgrade to 6.8.3 +- Drop the ghc682-style naming scheme, obsolete those packages +- Manually strip binaries + * Tue Apr 8 2008 Jens Petersen - 6.8.2-10 - another rebuild attempt From 34b478a7fd4e8c7a9cc8c84d22c9369e496e4298 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Thu, 19 Jun 2008 02:41:10 +0000 Subject: [PATCH 044/530] Remove unnecessary dependency on alex --- ghc-6.8.3-libraries-config.patch | 3 +-- ghc.spec | 5 ++++- 2 files changed, 5 insertions(+), 3 deletions(-) diff --git a/ghc-6.8.3-libraries-config.patch b/ghc-6.8.3-libraries-config.patch index f9e395a..e463d4b 100644 --- a/ghc-6.8.3-libraries-config.patch +++ b/ghc-6.8.3-libraries-config.patch @@ -1,10 +1,9 @@ --- ghc-6.8.3/libraries/Makefile~ 2008-06-17 23:10:28.000000000 -0700 +++ ghc-6.8.3/libraries/Makefile 2008-06-17 23:21:21.000000000 -0700 -@@ -256,6 +256,9 @@ +@@ -256,6 +256,8 @@ --with-hc-pkg=../../utils/ghc-pkg/ghc-pkg-inplace \ --with-hsc2hs=../../utils/hsc2hs/hsc2hs-inplace \ --with-ld=$(LD) \ -+ --with-alex=$(ALEX) \ + --with-haddock=$(HADDOCK) \ + --with-happy=$(HAPPY) \ --haddock-options="--use-contents=../index.html \ diff --git a/ghc.spec b/ghc.spec index 6fc0ca5..d9e6266 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.8.3 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -209,6 +209,9 @@ fi %changelog +* Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-2 +- Remove unnecessary dependency on alex + * Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-1 - Upgrade to 6.8.3 - Drop the ghc682-style naming scheme, obsolete those packages From 860e5f3f03b60389d963a4792ec865d5990808fd Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Thu, 19 Jun 2008 03:43:53 +0000 Subject: [PATCH 045/530] More build fixes --- ghc-6.8.3-libraries-config.patch | 11 +++++++++++ ghc.spec | 12 +++++++++++- 2 files changed, 22 insertions(+), 1 deletion(-) diff --git a/ghc-6.8.3-libraries-config.patch b/ghc-6.8.3-libraries-config.patch index e463d4b..451ced3 100644 --- a/ghc-6.8.3-libraries-config.patch +++ b/ghc-6.8.3-libraries-config.patch @@ -9,3 +9,14 @@ --haddock-options="--use-contents=../index.html \ --use-index=../doc-index.html" \ $(FLAGGED_CONFIGURE_ARGS) \ +--- ghc-6.8.3/libraries/gen_contents_index~ 2008-06-18 20:40:39.000000000 -0700 ++++ ghc-6.8.3/libraries/gen_contents_index 2008-06-18 20:40:50.000000000 -0700 +@@ -22,7 +22,7 @@ + done + + # Now create the combined contents and index pages +-haddock --gen-index --gen-contents -o . \ ++haddock-0.9 --gen-index --gen-contents -o . \ + -t "Haskell Hierarchical Libraries" \ + $HADDOCK_ARGS + diff --git a/ghc.spec b/ghc.spec index d9e6266..060a67f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.8.3 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -130,6 +130,12 @@ pushd ${RPM_BUILD_ROOT}/%{_libexecdir}/%{name}-%{version} strip cgprof ghc-%{version} ghc-pkg.bin hsc2hs-bin unlit popd +pushd ${RPM_BUILD_ROOT}/%{_libdir}/%{name}-%{version} +for i in ../../libexec/%{name}-%{version}/*; do + ln -s $i . +done +popd + %if %{build_doc} make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs if [ -d ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries ]; then @@ -209,6 +215,10 @@ fi %changelog +* Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-3 +- Add symlinks from _libdir, where ghc looks, to _libexecdir +- Patch libraries/gen_contents_index to use haddock-0.9 + * Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-2 - Remove unnecessary dependency on alex From d85f6b0a8416b08917d453d183f8d3ad59166473 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Sep 2008 06:00:51 +0000 Subject: [PATCH 046/530] - add macros.ghc for new Haskell Packaging Guidelines (#460304) --- ghc-rpm-macros.ghc | 57 ++++++++++++++++++++++++++++++++++++++++++++++ ghc.spec | 11 ++++++++- 2 files changed, 67 insertions(+), 1 deletion(-) create mode 100644 ghc-rpm-macros.ghc diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc new file mode 100644 index 0000000..d91b7e1 --- /dev/null +++ b/ghc-rpm-macros.ghc @@ -0,0 +1,57 @@ +%cabal %{_bindir}/runhaskell Setup + +%cabal_configure \ +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --libsubdir='$compiler/$pkgid' + +%cabal_build \ +%cabal build \ +%{nil} + +%cabal_makefile \ +%cabal makefile -f cabal-rpm.mk \ +make -f cabal-rpm.mk %{_smp_mflags} \ +%{nil} + +%cabal_haddock \ +%cabal haddock \ +%{nil} + +%cabal_install \ +%cabal copy --destdir=${RPM_BUILD_ROOT} \ +%{nil} + +%ghc_gen_filelists() \ +rm -f %1.files %1-prof.files \ +echo '%defattr(-,root,root,-)' > %1-prof.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ +echo '%defattr(-,root,root,-)' > %1.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1.files \ +sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1.files %1-prof.files \ +%{nil} + +%ghc_gen_scripts \ +%cabal register --gen-script \ +%cabal unregister --gen-script \ +%{nil} + +%ghc_install_scripts \ +install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ +%{nil} + +%ghc_preinst_script \ +[ "$1" = 2 ] && %{pkg_libdir}/unregister.sh >&/dev/null || : \ +%{nil} + +%ghc_postinst_script \ +%{pkg_libdir}/register.sh >&/dev/null \ +%{nil} + +%ghc_preun_script \ +%{pkg_libdir}/unregister.sh >&/dev/null \ +%{nil} + +%ghc_postun_script \ +[ "$1" = 1 ] && %{pkg_libdir}/register.sh >& /dev/null || : \ +%{nil} + diff --git a/ghc.spec b/ghc.spec index 060a67f..f6c5a7a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.8.3 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -24,6 +24,7 @@ License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src-extralibs.tar.bz2 +Source2: ghc-rpm-macros.ghc Patch0: ghc-6.8.3-libraries-config.patch URL: http://haskell.org/ghc/ Requires: chkconfig, gcc, gmp-devel, readline-devel @@ -145,6 +146,10 @@ fi cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries %endif +# install rpm macros +mkdir -p ${RPM_BUILD_ROOT}/%{_systemconfdir}/rpm/macros.ghc +cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_systemconfdir}/rpm/macros.ghc + SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT @@ -197,6 +202,7 @@ fi %doc ANNOUNCE HACKING LICENSE README %doc %{_mandir}/man1/ghc.* %{_bindir}/* +%{_systemconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %ghost %{_libdir}/ghc-%{version}/package.conf.old @@ -215,6 +221,9 @@ fi %changelog +* Wed Sep 17 2008 Jens Petersen - 6.8.3-4 +- add macros.ghc for new Haskell Packaging Guidelines (#460304) + * Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-3 - Add symlinks from _libdir, where ghc looks, to _libexecdir - Patch libraries/gen_contents_index to use haddock-0.9 From 97f36761c3a014cada6d36dd1924168ad7b9e024 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Sep 2008 07:11:56 +0000 Subject: [PATCH 047/530] fix writing of _sysconfdir --- ghc.spec | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index f6c5a7a..9af74aa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -147,9 +147,9 @@ cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries %endif # install rpm macros -mkdir -p ${RPM_BUILD_ROOT}/%{_systemconfdir}/rpm/macros.ghc -cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_systemconfdir}/rpm/macros.ghc - +mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc +cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc + SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT @@ -202,7 +202,7 @@ fi %doc ANNOUNCE HACKING LICENSE README %doc %{_mandir}/man1/ghc.* %{_bindir}/* -%{_systemconfdir}/rpm/macros.ghc +%{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %ghost %{_libdir}/ghc-%{version}/package.conf.old From 2a4aeca5ccbf5b1ce6038674c1d6f2d9cf0fb81d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Sep 2008 07:34:44 +0000 Subject: [PATCH 048/530] - bring back including haddock-generated lib docs, now under docdir/ghc - fix macros.ghc filepath (#460304) - spec file cleanups: - fix the source urls back - drop requires chkconfig - do not override __spec_install_post - override _target_platform so we can use %%configure - setup docs building in build.mk - no longer need to remove network/include/Typeable.h - install binaries under libdir not libexec - remove hsc2hs and runhaskell binaries since are alternatives --- ghc.spec | 110 ++++++++++++++++++++----------------------------------- 1 file changed, 39 insertions(+), 71 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9af74aa..4e58fd1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,32 +2,20 @@ %define build_prof 1 %define build_doc 1 -# Fixing packaging problems can be a tremendous pain because it -# generally requires a complete rebuild, which takes hours. To offset -# the misery, do a complete build once using "rpmbuild -bc", then copy -# your built tree to a directory of the same name suffixed with -# ".built", using "cp -al". Finally, set this variable, and it will -# copy the already-built tree into place during build instead of -# actually doing the build. -# -# Obviously, this can only work if you leave the build section -# completely untouched between builds. -%define package_debugging 0 - Name: ghc Version: 6.8.3 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 License: BSD Group: Development/Languages -Source0: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src.tar.bz2 -Source1: http://www.haskell.org/ghc/dist/stable/dist/ghc-%{version}-src-extralibs.tar.bz2 +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc Patch0: ghc-6.8.3-libraries-config.patch URL: http://haskell.org/ghc/ -Requires: chkconfig, gcc, gmp-devel, readline-devel +Requires: gcc, gmp-devel, readline-devel BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66 BuildRequires: ghc, happy, sed @@ -75,85 +63,51 @@ you like to have local access to the documentation in HTML format. # the debuginfo subpackage is currently empty anyway, so don't generate it %define debug_package %{nil} -%define __spec_install_post /usr/lib/rpm/brp-compress %prep %setup -q -n %{name}-%{version} -b1 - -%patch0 -p1 -b .hdkl +%patch0 -p1 -b .0-haddock~ %build -%if %{package_debugging} -cd .. -rm -rf %{name}-%{version} -cp -al %{name}-%{version}.built %{name}-%{version} -cd %{name}-%{version} -exit 0 -%endif - %if !%{build_prof} echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif -HaddockCmd=%{_bindir}/haddock-0.9 \ -./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ - --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ - --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ - --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} - -cat <> mk/build.mk -docdir := %{_docdir}/%{name}-%{version} -htmldir := \$(docdir) -dvidir := \$(docdir) -pdfdir := \$(docdir) -psdir := \$(docdir) -HADDOCK_PATH_HACK - -# drop truncated copy of header (#222865) -rm libraries/network/include/Typeable.h - -make %{_smp_mflags} all libexecdir=%{_libexecdir} +%if %{build_doc} +echo "XMLDocWays = html" >> mk/build.mk +echo "HADDOCK_DOCS = YES" >> mk/build.mk +%endif + +export HaddockCmd=%{_bindir}/haddock-0.9 +# workaround ghc configure script hysteria about archs +%define _target_platform %{_build} +%configure + +make %{_smp_mflags} +make %{_smp_mflags} -C libraries + %if %{build_doc} make %{_smp_mflags} html -make %{_smp_mflags} -C libraries HADDOCK_DOCS=YES -( cd libraries/Cabal && docbook2html doc/Cabal.xml --output doc/Cabal ) %endif %install rm -rf $RPM_BUILD_ROOT -make DESTDIR=${RPM_BUILD_ROOT} libdir=%{_libdir}/%{name}-%{version} \ - libexecdir=%{_libexecdir}/%{name}-%{version} install - -pushd ${RPM_BUILD_ROOT}/%{_libexecdir}/%{name}-%{version} -strip cgprof ghc-%{version} ghc-pkg.bin hsc2hs-bin unlit -popd - -pushd ${RPM_BUILD_ROOT}/%{_libdir}/%{name}-%{version} -for i in ../../libexec/%{name}-%{version}/*; do - ln -s $i . -done -popd +make DESTDIR=${RPM_BUILD_ROOT} install %if %{build_doc} -make DESTDIR=${RPM_BUILD_ROOT} XMLDocWays="html" HADDOCK_DOCS=YES install-docs -if [ -d ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries ]; then - mv ${RPM_BUILD_ROOT}/%{_docdir}/%{name}/libraries \ - ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version} -fi -cp libraries/*.html ${RPM_BUILD_ROOT}/%{_docdir}/%{name}-%{version}/libraries +make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif # install rpm macros -mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc +mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} .%{_libexecdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) ) # make paths absolute (filter "./usr" to "/usr") @@ -167,7 +121,8 @@ cat rpm-dir.files rpm-prof.files > rpm-prof-filelist # create package.conf.old touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old -mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs-ghc +# these are handled as alternatives +rm ${RPM_BUILD_ROOT}%{_bindir}/{hsc2hs,runhaskell} %clean rm -rf $RPM_BUILD_ROOT @@ -216,12 +171,25 @@ fi %if %{build_doc} %files doc %defattr(-,root,root,-) -%{_docdir}/%{name}-%{version} +%{_docdir}/%{name} %endif %changelog -* Wed Sep 17 2008 Jens Petersen - 6.8.3-4 +* Wed Sep 24 2008 Jens Petersen - 6.8.3-5.fc10 +- bring back haddock-generated lib docs, now under docdir/ghc +- fix macros.ghc filepath (#460304) +- spec file cleanups: +- fix the source urls back +- drop requires chkconfig +- do not override __spec_install_post +- override _target_platform so we can use %%configure +- setup docs building in build.mk +- no longer need to remove network/include/Typeable.h +- install binaries under libdir not libexec +- remove hsc2hs and runhaskell binaries since are alternatives + +* Wed Sep 17 2008 Jens Petersen - 6.8.3-4.fc10 - add macros.ghc for new Haskell Packaging Guidelines (#460304) * Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-3 From c5b8789b8e361ea3d0f2361ccfa84d1abcbfb4f7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Sep 2008 07:36:11 +0000 Subject: [PATCH 049/530] tweak docs changelog entries --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 4e58fd1..4d5886b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -177,7 +177,7 @@ fi %changelog * Wed Sep 24 2008 Jens Petersen - 6.8.3-5.fc10 -- bring back haddock-generated lib docs, now under docdir/ghc +- bring back including haddock-generated lib docs, now under docdir/ghc - fix macros.ghc filepath (#460304) - spec file cleanups: - fix the source urls back From 6a740e49cf788f5855c2922ae28a1930fa9d9fcd Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Sep 2008 08:03:22 +0000 Subject: [PATCH 050/530] revert back from using %configure since it fails on ppc --- ghc.spec | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4d5886b..8c5070b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -80,9 +80,12 @@ echo "HADDOCK_DOCS = YES" >> mk/build.mk %endif export HaddockCmd=%{_bindir}/haddock-0.9 -# workaround ghc configure script hysteria about archs -%define _target_platform %{_build} -%configure + +./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ + --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ + --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ + --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} make %{_smp_mflags} make %{_smp_mflags} -C libraries @@ -183,7 +186,6 @@ fi - fix the source urls back - drop requires chkconfig - do not override __spec_install_post -- override _target_platform so we can use %%configure - setup docs building in build.mk - no longer need to remove network/include/Typeable.h - install binaries under libdir not libexec From 2e71ab898ca066e759d39d2d86a5e21dfd311a52 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 26 Sep 2008 07:14:14 +0000 Subject: [PATCH 051/530] bring back %package_debugging for bos since it does "more" than --short-circuit --- ghc.spec | 21 +++++++++++++++++++++ 1 file changed, 21 insertions(+) diff --git a/ghc.spec b/ghc.spec index 8c5070b..2947881 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,6 +2,18 @@ %define build_prof 1 %define build_doc 1 +# Fixing packaging problems can be a tremendous pain because it +# generally requires a complete rebuild, which takes hours. To offset +# the misery, do a complete build once using "rpmbuild -bc", then copy +# your built tree to a directory of the same name suffixed with +# ".built", using "cp -al". Finally, set this variable, and it will +# copy the already-built tree into place during build instead of +# actually doing the build. +# +# Obviously, this can only work if you leave the build section +# completely untouched between builds. +%define package_debugging 0 + Name: ghc Version: 6.8.3 Release: 5%{?dist} @@ -69,6 +81,15 @@ you like to have local access to the documentation in HTML format. %patch0 -p1 -b .0-haddock~ %build +# hack for building a local test package quickly from a prebuilt tree +%if %{package_debugging} +pushd .. +rm -rf %{name}-%{version} +cp -al %{name}-%{version}.built %{name}-%{version} +popd +exit 0 +%endif + %if !%{build_prof} echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk From ef6ff25c36b21ab292ed7d928ee79e8cbc34fe61 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 1 Oct 2008 22:26:01 +0000 Subject: [PATCH 052/530] Don't remove hsc2hs, rename it --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2947881..f0fa7a8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.8.3 -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -146,7 +146,8 @@ cat rpm-dir.files rpm-prof.files > rpm-prof-filelist touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old # these are handled as alternatives -rm ${RPM_BUILD_ROOT}%{_bindir}/{hsc2hs,runhaskell} +mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs-ghc +rm ${RPM_BUILD_ROOT}%{_bindir}/runhaskell %clean rm -rf $RPM_BUILD_ROOT @@ -200,6 +201,9 @@ fi %changelog +* Wed Oct 1 2008 Bryan O'Sullivan 6.8.3-6.fc10 +* Rename hsc2hs to hsc2hs-ghc so the alternatives symlink to it will work + * Wed Sep 24 2008 Jens Petersen - 6.8.3-5.fc10 - bring back including haddock-generated lib docs, now under docdir/ghc - fix macros.ghc filepath (#460304) From a8b8189107f1f08fb72a6fe221d53109d113c30b Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 13 Oct 2008 03:05:05 +0000 Subject: [PATCH 053/530] Port F-10 changes to devel --- ghc-6.8.3-libraries-config.patch | 22 --------------------- ghc.spec | 33 ++++++++++++++++---------------- sources | 4 ++-- 3 files changed, 19 insertions(+), 40 deletions(-) delete mode 100644 ghc-6.8.3-libraries-config.patch diff --git a/ghc-6.8.3-libraries-config.patch b/ghc-6.8.3-libraries-config.patch deleted file mode 100644 index 451ced3..0000000 --- a/ghc-6.8.3-libraries-config.patch +++ /dev/null @@ -1,22 +0,0 @@ ---- ghc-6.8.3/libraries/Makefile~ 2008-06-17 23:10:28.000000000 -0700 -+++ ghc-6.8.3/libraries/Makefile 2008-06-17 23:21:21.000000000 -0700 -@@ -256,6 +256,8 @@ - --with-hc-pkg=../../utils/ghc-pkg/ghc-pkg-inplace \ - --with-hsc2hs=../../utils/hsc2hs/hsc2hs-inplace \ - --with-ld=$(LD) \ -+ --with-haddock=$(HADDOCK) \ -+ --with-happy=$(HAPPY) \ - --haddock-options="--use-contents=../index.html \ - --use-index=../doc-index.html" \ - $(FLAGGED_CONFIGURE_ARGS) \ ---- ghc-6.8.3/libraries/gen_contents_index~ 2008-06-18 20:40:39.000000000 -0700 -+++ ghc-6.8.3/libraries/gen_contents_index 2008-06-18 20:40:50.000000000 -0700 -@@ -22,7 +22,7 @@ - done - - # Now create the combined contents and index pages --haddock --gen-index --gen-contents -o . \ -+haddock-0.9 --gen-index --gen-contents -o . \ - -t "Haskell Hierarchical Libraries" \ - $HADDOCK_ARGS - diff --git a/ghc.spec b/ghc.spec index f0fa7a8..8cfd531 100644 --- a/ghc.spec +++ b/ghc.spec @@ -15,8 +15,8 @@ %define package_debugging 0 Name: ghc -Version: 6.8.3 -Release: 6%{?dist} +Version: 6.10.0.20081007 +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -25,19 +25,14 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc -Patch0: ghc-6.8.3-libraries-config.patch URL: http://haskell.org/ghc/ -Requires: gcc, gmp-devel, readline-devel +Requires: gcc, gmp-devel, libedit-devel BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, ghc661, ghc66 +Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 BuildRequires: ghc, happy, sed -BuildRequires: gmp-devel, readline-devel -# X11 is no longer in ghc extralibs -#BuildRequires: libX11-devel, libXt-devel -BuildRequires: freeglut-devel, openal-devel +BuildRequires: gmp-devel, libedit-devel %if %{build_doc} -# haddock generates docs in libraries, but haddock 2.0 is not compatible -BuildRequires: libxslt, docbook-style-xsl, haddock09 +BuildRequires: libxslt, docbook-style-xsl %endif %description @@ -78,7 +73,6 @@ you like to have local access to the documentation in HTML format. %prep %setup -q -n %{name}-%{version} -b1 -%patch0 -p1 -b .0-haddock~ %build # hack for building a local test package quickly from a prebuilt tree @@ -100,8 +94,6 @@ echo "XMLDocWays = html" >> mk/build.mk echo "HADDOCK_DOCS = YES" >> mk/build.mk %endif -export HaddockCmd=%{_bindir}/haddock-0.9 - ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -201,8 +193,17 @@ fi %changelog -* Wed Oct 1 2008 Bryan O'Sullivan 6.8.3-6.fc10 -* Rename hsc2hs to hsc2hs-ghc so the alternatives symlink to it will work +* Sun Oct 12 2008 Bryan O'Sullivan - 6.10.0.20081007-2.fc10 +- Use libedit in preference to readline, for BSD license consistency +- With haddock bundled now, obsolete standalone versions (but not haddock09) +- Drop obsolete freeglut-devel, openal-devel, and haddock09 dependencies + +* Sun Oct 12 2008 Bryan O'Sullivan - 6.10.0.20081007-1.fc10 +- Update to 6.10.1 release candidate 1 + +* Wed Oct 1 2008 Bryan O'Sullivan - 6.10.0.20080921-1.fc10 +- Drop unneeded haddock patch +- Rename hsc2hs to hsc2hs-ghc so the alternatives symlink to it will work * Wed Sep 24 2008 Jens Petersen - 6.8.3-5.fc10 - bring back including haddock-generated lib docs, now under docdir/ghc diff --git a/sources b/sources index cf8f101..f15cb81 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -5ac72f5d5433151cf6b718dc6601dc41 ghc-6.8.3-src-extralibs.tar.bz2 -dfa31028b4d06d1d226f55fe3a2ab7b3 ghc-6.8.3-src.tar.bz2 +4350d1f8bea53f713732d10a7a9133f6 ghc-6.10.0.20081007-src.tar.bz2 +59136b86bafbdc4d32a645d3d7a8fa46 ghc-6.10.0.20081007-src-extralibs.tar.bz2 From 3c43e3814fa433f164a459e1fb9aea95e42aac3e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 13 Oct 2008 05:20:47 +0000 Subject: [PATCH 054/530] - provide haddock = 2.2.2 - add selinux file context for unconfined_execmem following darcs package - post requires policycoreutils --- ghc.spec | 15 +++++++++++++-- 1 file changed, 13 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 8cfd531..74108d0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -27,8 +27,11 @@ Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs Source2: ghc-rpm-macros.ghc URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel, libedit-devel +Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 +# introduced for f11 and to be removed for f13: +Provides: haddock = 2.2.2 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel %if %{build_doc} @@ -138,13 +141,16 @@ cat rpm-dir.files rpm-prof.files > rpm-prof-filelist touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old # these are handled as alternatives -mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs-ghc +mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs{,-ghc} rm ${RPM_BUILD_ROOT}%{_bindir}/runhaskell %clean rm -rf $RPM_BUILD_ROOT %post +semanage fcontext -a -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/ghc >/dev/null 2>&1 || : +restorecon %{_libdir}/ghc-%{version}/ghc >/dev/null + # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: # @@ -193,6 +199,11 @@ fi %changelog +* Mon Oct 13 2008 Jens Petersen - 6.10.0.20081007-3 +- provide haddock = 2.2.2 +- add selinux file context for unconfined_execmem following darcs package +- post requires policycoreutils + * Sun Oct 12 2008 Bryan O'Sullivan - 6.10.0.20081007-2.fc10 - Use libedit in preference to readline, for BSD license consistency - With haddock bundled now, obsolete standalone versions (but not haddock09) From 354d10e225640c7ffb2bb25b1900c62c74271fb3 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Tue, 14 Oct 2008 18:55:27 +0000 Subject: [PATCH 055/530] Generate haddocks after installing ghc-doc --- ghc-rpm-macros.ghc | 8 ++++++++ ghc.spec | 18 +++++++++++++++++- 2 files changed, 25 insertions(+), 1 deletion(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index d91b7e1..82c6bf7 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -55,3 +55,11 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ [ "$1" = 1 ] && %{pkg_libdir}/register.sh >& /dev/null || : \ %{nil} +%ghc_haddock_reindex \ +if [ -f /usr/bin/haddock -a -d /usr/share/doc/ghc/libraries ]; then \ +cd /usr/share/doc/ghc/libraries && \ +haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \ +$(find . \( \( -path ./ghc -o -path ./ghc-prim \) -prune \) -o \( -name '*.haddock' -print \) \ +| sed 's!.*/\([^/]*\).haddock!--read-interface=\1,\0!'); \ +fi \ +%{nil} diff --git a/ghc.spec b/ghc.spec index 74108d0..f745dbe 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -168,6 +168,11 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 + +%post doc +%ghc_haddock_reindex + + %preun if test "$1" = 0; then update-alternatives --remove runhaskell %{_bindir}/runghc @@ -195,10 +200,21 @@ fi %files doc %defattr(-,root,root,-) %{_docdir}/%{name} +%ghost %{_docdir}/%{name}/libraries/doc-index.html +%ghost %{_docdir}/%{name}/libraries/haddock.css +%ghost %{_docdir}/%{name}/libraries/haddock-util.js +%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif +%ghost %{_docdir}/%{name}/libraries/index.html +%ghost %{_docdir}/%{name}/libraries/minus.gif +%ghost %{_docdir}/%{name}/libraries/plus.gif %endif %changelog +* Sun Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-4 +- Add ghc_haddock_reindex macro +- Generate haddock index after installing ghc-doc package + * Mon Oct 13 2008 Jens Petersen - 6.10.0.20081007-3 - provide haddock = 2.2.2 - add selinux file context for unconfined_execmem following darcs package From 8a484b3e878c432e6c0d6df94b5419eb23b02e20 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Tue, 14 Oct 2008 21:32:36 +0000 Subject: [PATCH 056/530] Try to fix doc indexing --- ghc-rpm-macros.ghc | 7 +++++-- ghc.spec | 12 +++++++++--- 2 files changed, 14 insertions(+), 5 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 82c6bf7..0b0195b 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -20,6 +20,9 @@ make -f cabal-rpm.mk %{_smp_mflags} \ %cabal copy --destdir=${RPM_BUILD_ROOT} \ %{nil} +%ghc_cabal_configure \ +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/ghc/libraries/%{name} --libsubdir='$compiler/$pkgid' + %ghc_gen_filelists() \ rm -f %1.files %1-prof.files \ echo '%defattr(-,root,root,-)' > %1-prof.files \ @@ -56,8 +59,8 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ %{nil} %ghc_haddock_reindex \ -if [ -f /usr/bin/haddock -a -d /usr/share/doc/ghc/libraries ]; then \ -cd /usr/share/doc/ghc/libraries && \ +if [ -f %{_bindir}/haddock -a -d %{_docdir}/ghc/libraries ]; then \ +cd %{_docdir}/ghc/libraries && \ haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \ $(find . \( \( -path ./ghc -o -path ./ghc-prim \) -prune \) -o \( -name '*.haddock' -print \) \ | sed 's!.*/\([^/]*\).haddock!--read-interface=\1,\0!'); \ diff --git a/ghc.spec b/ghc.spec index f745dbe..793abef 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -170,7 +170,10 @@ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %post doc -%ghc_haddock_reindex +cd %{_docdir}/ghc/libraries && \ +haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \ +$(find . \( \( -path ./ghc -o -path ./ghc-prim \) -prune \) -o \( -name '*.haddock' -print \) \ +| sed 's!.*/\([^/]*\).haddock!--read-interface=\1,\0!') %preun @@ -211,7 +214,10 @@ fi %changelog -* Sun Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-4 +* Tue Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-5 +- Don't use a macro to update the docs for the main doc package + +* Tue Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-4 - Add ghc_haddock_reindex macro - Generate haddock index after installing ghc-doc package From cb5a89f23cccf7611dfd195aa1c335e2d05ba0f8 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 15 Oct 2008 03:42:23 +0000 Subject: [PATCH 057/530] Update macros to put haddock bits in the right place --- ghc-rpm-macros.ghc | 16 ++++++++-------- ghc.spec | 5 ++++- 2 files changed, 12 insertions(+), 9 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 0b0195b..c2bb66a 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,7 +1,7 @@ %cabal %{_bindir}/runhaskell Setup %cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --libsubdir='$compiler/$pkgid' +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{_docdir}/%{hsc_name}/libraries/%{pkg_name} --haddockdir=%{_docdir}/%{hsc_name}/libraries/%{pkg_name} --libsubdir='$compiler/$pkgid' %cabal_build \ %cabal build \ @@ -17,7 +17,7 @@ make -f cabal-rpm.mk %{_smp_mflags} \ %{nil} %cabal_install \ -%cabal copy --destdir=${RPM_BUILD_ROOT} \ +%cabal copy --destdir=${RPM_BUILD_ROOT} -v \ %{nil} %ghc_cabal_configure \ @@ -58,11 +58,11 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ [ "$1" = 1 ] && %{pkg_libdir}/register.sh >& /dev/null || : \ %{nil} -%ghc_haddock_reindex \ -if [ -f %{_bindir}/haddock -a -d %{_docdir}/ghc/libraries ]; then \ -cd %{_docdir}/ghc/libraries && \ -haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \ -$(find . \( \( -path ./ghc -o -path ./ghc-prim \) -prune \) -o \( -name '*.haddock' -print \) \ -| sed 's!.*/\([^/]*\).haddock!--read-interface=\1,\0!'); \ +%ghc_reindex_haddock \ +if [ -f %{_bindir}/haddock -a -d %{_docdir}/%{hsc_name}/libraries ]; then \ +cd %{_docdir}/%{hsc_name}/libraries && \ +haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \\\ +$(find . \\( \\( -path ./ghc -o -path ./ghc-prim \\) -prune \\) -o \\( -name '*.haddock' -print \\) \\\ +| sed 's!.*/\\([^/]*\\).haddock!--read-interface=\\1,\\0!'); \ fi \ %{nil} diff --git a/ghc.spec b/ghc.spec index 793abef..5521850 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -214,6 +214,9 @@ fi %changelog +* Tue Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-6 +- Update macros to install html and haddock bits in the right places + * Tue Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-5 - Don't use a macro to update the docs for the main doc package From 4b8e6f699e96945797197390feafe1cb0d5550d8 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 15 Oct 2008 03:52:24 +0000 Subject: [PATCH 058/530] Remove accidental bogosity experiment --- ghc-rpm-macros.ghc | 3 --- 1 file changed, 3 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index c2bb66a..b22f59c 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -20,9 +20,6 @@ make -f cabal-rpm.mk %{_smp_mflags} \ %cabal copy --destdir=${RPM_BUILD_ROOT} -v \ %{nil} -%ghc_cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/ghc/libraries/%{name} --libsubdir='$compiler/$pkgid' - %ghc_gen_filelists() \ rm -f %1.files %1-prof.files \ echo '%defattr(-,root,root,-)' > %1-prof.files \ From c7ae1a2bd58506763e1aa22627f0ae6ea08494bc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 23 Oct 2008 03:00:41 +0000 Subject: [PATCH 059/530] - use gen_contents_index to re-index haddock - add %%pkg_docdir to cabal_configure - requires(post) ghc for haddock for doc - improve doc file lists - no longer need to create ghost package.conf.old - remove or rename alternatives files more consistently --- .cvsignore | 4 ++-- ghc-rpm-macros.ghc | 9 ++------- ghc.spec | 48 +++++++++++++++++++++++++++++----------------- 3 files changed, 34 insertions(+), 27 deletions(-) diff --git a/.cvsignore b/.cvsignore index 245433c..870e85c 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.8.3-src-extralibs.tar.bz2 -ghc-6.8.3-src.tar.bz2 +ghc-6.10.0.20081007-src.tar.bz2 +ghc-6.10.0.20081007-src-extralibs.tar.bz2 diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index b22f59c..a9fc91b 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,7 +1,7 @@ %cabal %{_bindir}/runhaskell Setup %cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{_docdir}/%{hsc_name}/libraries/%{pkg_name} --haddockdir=%{_docdir}/%{hsc_name}/libraries/%{pkg_name} --libsubdir='$compiler/$pkgid' +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{pkg_docdir} --haddockdir=%{pkg_docdir} --libsubdir='$compiler/$pkgid' %cabal_build \ %cabal build \ @@ -56,10 +56,5 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ %{nil} %ghc_reindex_haddock \ -if [ -f %{_bindir}/haddock -a -d %{_docdir}/%{hsc_name}/libraries ]; then \ -cd %{_docdir}/%{hsc_name}/libraries && \ -haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \\\ -$(find . \\( \\( -path ./ghc -o -path ./ghc-prim \\) -prune \\) -o \\( -name '*.haddock' -print \\) \\\ -| sed 's!.*/\\([^/]*\\).haddock!--read-interface=\\1,\\0!'); \ -fi \ +( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : \ %{nil} diff --git a/ghc.spec b/ghc.spec index 5521850..a0207ac 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 6%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -65,6 +65,8 @@ needed. Summary: Documentation for GHC Group: Development/Languages Requires: %{name} = %{version}-%{release} +# for haddock +Requires(post): %{name} = %{version}-%{release} %description doc Preformatted documentation for the Glorious Glasgow Haskell @@ -126,7 +128,8 @@ cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf' -fprint $SRC_TOP/rpm-lib.files \) + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf*' -fprint $SRC_TOP/rpm-lib.files \) + find .%{_docdir}/%{name}/* -type d ! -name libraries > $SRC_TOP/rpm-doc-dir.files ) # make paths absolute (filter "./usr" to "/usr") @@ -137,19 +140,21 @@ cat rpm-dir.files rpm-lib.files > rpm-base-filelist cat rpm-dir.files rpm-prof.files > rpm-prof-filelist %endif -# create package.conf.old -touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old - # these are handled as alternatives -mv ${RPM_BUILD_ROOT}%{_bindir}/hsc2hs{,-ghc} -rm ${RPM_BUILD_ROOT}%{_bindir}/runhaskell +for i in hsc2hs runhaskell; do + if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then + rm ${RPM_BUILD_ROOT}%{_bindir}/$i + else + mv ${RPM_BUILD_ROOT}%{_bindir}/$i{,-ghc} + fi +done %clean rm -rf $RPM_BUILD_ROOT %post semanage fcontext -a -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/ghc >/dev/null 2>&1 || : -restorecon %{_libdir}/ghc-%{version}/ghc >/dev/null +restorecon %{_libdir}/ghc-%{version}/ghc # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: @@ -170,11 +175,7 @@ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %post doc -cd %{_docdir}/ghc/libraries && \ -haddock --gen-index --gen-contents -o . -t 'Haskell Hierarchical Libraries' \ -$(find . \( \( -path ./ghc -o -path ./ghc-prim \) -prune \) -o \( -name '*.haddock' -print \) \ -| sed 's!.*/\([^/]*\).haddock!--read-interface=\1,\0!') - +( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : %preun if test "$1" = 0; then @@ -200,9 +201,12 @@ fi %if %{build_doc} -%files doc +%files doc -f rpm-doc-dir.files %defattr(-,root,root,-) -%{_docdir}/%{name} +%dir %{_docdir}/%{name} +%{_docdir}/%{name}/index.html +%{_docdir}/%{name}/libraries/gen_contents_index +%dir %{_docdir}/%{name}/libraries %ghost %{_docdir}/%{name}/libraries/doc-index.html %ghost %{_docdir}/%{name}/libraries/haddock.css %ghost %{_docdir}/%{name}/libraries/haddock-util.js @@ -214,6 +218,14 @@ fi %changelog +* Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-7 +- use gen_contents_index to re-index haddock +- add %%pkg_docdir to cabal_configure +- requires(post) ghc for haddock for doc +- improve doc file lists +- no longer need to create ghost package.conf.old +- remove or rename alternatives files more consistently + * Tue Oct 14 2008 Bryan O'Sullivan - 6.10.0.20081007-6 - Update macros to install html and haddock bits in the right places @@ -241,7 +253,7 @@ fi - Drop unneeded haddock patch - Rename hsc2hs to hsc2hs-ghc so the alternatives symlink to it will work -* Wed Sep 24 2008 Jens Petersen - 6.8.3-5.fc10 +* Wed Sep 24 2008 Jens Petersen - 6.8.3-5 - bring back including haddock-generated lib docs, now under docdir/ghc - fix macros.ghc filepath (#460304) - spec file cleanups: @@ -251,9 +263,9 @@ fi - setup docs building in build.mk - no longer need to remove network/include/Typeable.h - install binaries under libdir not libexec -- remove hsc2hs and runhaskell binaries since are alternatives +- remove hsc2hs and runhaskell binaries since they are alternatives -* Wed Sep 17 2008 Jens Petersen - 6.8.3-4.fc10 +* Wed Sep 17 2008 Jens Petersen - 6.8.3-4 - add macros.ghc for new Haskell Packaging Guidelines (#460304) * Wed Jun 18 2008 Bryan O'Sullivan - 6.8.3-3 From a8cf709ba6cdaab6536779e43fa2daf14a6858d3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 23 Oct 2008 03:42:59 +0000 Subject: [PATCH 060/530] need to create ghost package.conf.old for ghc-6.10 --- ghc.spec | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a0207ac..2848b46 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -140,6 +140,9 @@ cat rpm-dir.files rpm-lib.files > rpm-base-filelist cat rpm-dir.files rpm-prof.files > rpm-prof-filelist %endif +# create package.conf.old +touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old + # these are handled as alternatives for i in hsc2hs runhaskell; do if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then @@ -218,6 +221,9 @@ fi %changelog +* Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-8 +- need to create ghost package.conf.old for ghc-6.10 + * Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-7 - use gen_contents_index to re-index haddock - add %%pkg_docdir to cabal_configure From ab507b7b807d3f82606fdc941a3dc709318837fa Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 23 Oct 2008 06:40:25 +0000 Subject: [PATCH 061/530] - cabal_configure does not need redundant --haddockdir - actually ghc-pkg no longer seems to create package.conf.old backups - include LICENSE in doc --- ghc-rpm-macros.ghc | 2 +- ghc.spec | 17 +++++++---------- 2 files changed, 8 insertions(+), 11 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index a9fc91b..65b0c24 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,7 +1,7 @@ %cabal %{_bindir}/runhaskell Setup %cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{pkg_docdir} --haddockdir=%{pkg_docdir} --libsubdir='$compiler/$pkgid' +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{pkg_docdir} --libsubdir='$compiler/$pkgid' %cabal_build \ %cabal build \ diff --git a/ghc.spec b/ghc.spec index 2848b46..838c143 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.0.20081007 -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -140,9 +140,6 @@ cat rpm-dir.files rpm-lib.files > rpm-base-filelist cat rpm-dir.files rpm-prof.files > rpm-prof-filelist %endif -# create package.conf.old -touch $RPM_BUILD_ROOT%{_libdir}/ghc-%{version}/package.conf.old - # these are handled as alternatives for i in hsc2hs runhaskell; do if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then @@ -176,7 +173,6 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 - %post doc ( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : @@ -186,7 +182,6 @@ if test "$1" = 0; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi - %files -f rpm-base-filelist %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README @@ -194,19 +189,17 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%ghost %{_libdir}/ghc-%{version}/package.conf.old - %if %{build_prof} %files prof -f rpm-prof-filelist %defattr(-,root,root,-) %endif - %if %{build_doc} %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) %dir %{_docdir}/%{name} +%{_docdir}/%{name}/LICENSE %{_docdir}/%{name}/index.html %{_docdir}/%{name}/libraries/gen_contents_index %dir %{_docdir}/%{name}/libraries @@ -219,8 +212,12 @@ fi %ghost %{_docdir}/%{name}/libraries/plus.gif %endif - %changelog +* Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-9 +- remove redundant --haddockdir from cabal_configure +- actually ghc-pkg no longer seems to create package.conf.old backups +- include LICENSE in doc + * Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-8 - need to create ghost package.conf.old for ghc-6.10 From 49ce8a29d13c7008f0c1c602566666a09686b6ae Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 23 Oct 2008 08:31:20 +0000 Subject: [PATCH 062/530] make ghc_reindex_haddock safer when ghc-doc not installed --- ghc-rpm-macros.ghc | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 65b0c24..599135d 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -56,5 +56,5 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ %{nil} %ghc_reindex_haddock \ -( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : \ +( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : \ %{nil} From 378558c59702de21eecfb6af65e5ab7858be1eb0 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 5 Nov 2008 04:32:03 +0000 Subject: [PATCH 063/530] ghc 6.10.1 release --- .cvsignore | 4 ++-- ghc.spec | 7 +++++-- sources | 4 ++-- 3 files changed, 9 insertions(+), 6 deletions(-) diff --git a/.cvsignore b/.cvsignore index 870e85c..57d613f 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.10.0.20081007-src.tar.bz2 -ghc-6.10.0.20081007-src-extralibs.tar.bz2 +ghc-6.10.1-src.tar.bz2 +ghc-6.10.1-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 838c143..011b56f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -15,8 +15,8 @@ %define package_debugging 0 Name: ghc -Version: 6.10.0.20081007 -Release: 9%{?dist} +Version: 6.10.1 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -213,6 +213,9 @@ fi %endif %changelog +* Tue Nov 04 2008 Bryan O'Sullivan - 6.10.1-1 +- Update to 6.10.1 in observance of President Obama + * Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-9 - remove redundant --haddockdir from cabal_configure - actually ghc-pkg no longer seems to create package.conf.old backups diff --git a/sources b/sources index f15cb81..9a920d0 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -4350d1f8bea53f713732d10a7a9133f6 ghc-6.10.0.20081007-src.tar.bz2 -59136b86bafbdc4d32a645d3d7a8fa46 ghc-6.10.0.20081007-src-extralibs.tar.bz2 +54c676a632b3d73cf526b06347522c32 ghc-6.10.1-src.tar.bz2 +4ff4590f1002ae1ff608874da8643c67 ghc-6.10.1-src-extralibs.tar.bz2 From cd0fae4df48f3256748a0b59daa031b9883aa4ba Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 5 Nov 2008 05:32:13 +0000 Subject: [PATCH 064/530] Fix a minor packaging glitch --- ghc.spec | 6 +++++- 1 file changed, 5 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 011b56f..3af591c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -210,9 +210,13 @@ fi %ghost %{_docdir}/%{name}/libraries/index.html %ghost %{_docdir}/%{name}/libraries/minus.gif %ghost %{_docdir}/%{name}/libraries/plus.gif +%ghost %{_docdir}/%{name}/libraries/prologue.txt %endif %changelog +* Tue Nov 04 2008 Bryan O'Sullivan - 6.10.1-2 +- Fix a minor packaging glitch + * Tue Nov 04 2008 Bryan O'Sullivan - 6.10.1-1 - Update to 6.10.1 in observance of President Obama From 6e900886a00cdfe631db6915c52f68d31bacd27b Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 5 Nov 2008 21:58:34 +0000 Subject: [PATCH 065/530] libraries/prologue.txt should not have been ghosted --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 3af591c..d022f8f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -202,6 +202,7 @@ fi %{_docdir}/%{name}/LICENSE %{_docdir}/%{name}/index.html %{_docdir}/%{name}/libraries/gen_contents_index +%{_docdir}/%{name}/libraries/prologue.txt %dir %{_docdir}/%{name}/libraries %ghost %{_docdir}/%{name}/libraries/doc-index.html %ghost %{_docdir}/%{name}/libraries/haddock.css @@ -210,10 +211,12 @@ fi %ghost %{_docdir}/%{name}/libraries/index.html %ghost %{_docdir}/%{name}/libraries/minus.gif %ghost %{_docdir}/%{name}/libraries/plus.gif -%ghost %{_docdir}/%{name}/libraries/prologue.txt %endif %changelog +* Wed Nov 05 2008 Bryan O'Sullivan - 6.10.1-3 +- libraries/prologue.txt should not have been ghosted + * Tue Nov 04 2008 Bryan O'Sullivan - 6.10.1-2 - Fix a minor packaging glitch From f20412293bf87a239bea876834b431c22765d246 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 5 Nov 2008 22:19:30 +0000 Subject: [PATCH 066/530] libraries/prologue.txt should not have been ghosted --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d022f8f..9b45047 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 From 6c9b784686334ec99b93b7a05bafa3773b194d21 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 11 Nov 2008 03:48:10 +0000 Subject: [PATCH 067/530] - fix broken urls to haddock docs created by gen_contents_index script - avoid haddock errors when upgrading by making doc post script posttrans --- ghc-6.10.1-gen_contexts_index.patch | 12 ++++++++++++ ghc.spec | 13 ++++++++++--- 2 files changed, 22 insertions(+), 3 deletions(-) create mode 100644 ghc-6.10.1-gen_contexts_index.patch diff --git a/ghc-6.10.1-gen_contexts_index.patch b/ghc-6.10.1-gen_contexts_index.patch new file mode 100644 index 0000000..aff35a3 --- /dev/null +++ b/ghc-6.10.1-gen_contexts_index.patch @@ -0,0 +1,12 @@ +diff -u ghc/libraries/gen_contents_index~ ghc/libraries/gen_contents_index +--- ghc-6.10.1/libraries/gen_contents_index~ 2008-11-06 11:18:45.000000000 +1000 ++++ ghc-6.10.1/libraries/gen_contents_index 2008-11-10 17:53:12.000000000 +1000 +@@ -23,7 +23,7 @@ + + for HADDOCK_FILE in $HADDOCK_FILES + do +- NAME=` echo "$HADDOCK_FILE" | sed 's#/dist/.*##' | sed 's#.*/##' ` ++ NAME=` echo "$HADDOCK_FILE" | sed 's#/dist/.*##' | sed 's#.*/##' | sed 's#\.haddock##' ` + HADDOCK_ARGS="$HADDOCK_ARGS --read-interface=$NAME,$HADDOCK_FILE" + NAMES="$NAMES $NAME" + done diff --git a/ghc.spec b/ghc.spec index 9b45047..c93357e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -37,6 +37,7 @@ BuildRequires: gmp-devel, libedit-devel %if %{build_doc} BuildRequires: libxslt, docbook-style-xsl %endif +Patch1: ghc-6.10.1-gen_contexts_index.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -78,6 +79,7 @@ you like to have local access to the documentation in HTML format. %prep %setup -q -n %{name}-%{version} -b1 +%patch1 -p1 -b .orig %build # hack for building a local test package quickly from a prebuilt tree @@ -173,11 +175,12 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 -%post doc +# posttrans to make sure any old documentation has been removed first +%posttrans doc ( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : %preun -if test "$1" = 0; then +if [ "$1" = 0 ]; then update-alternatives --remove runhaskell %{_bindir}/runghc update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi @@ -214,6 +217,10 @@ fi %endif %changelog +* Tue Nov 11 2008 Jens Petersen - 6.10.1-4 +- fix broken urls to haddock docs created by gen_contents_index script +- avoid haddock errors when upgrading by making doc post script posttrans + * Wed Nov 05 2008 Bryan O'Sullivan - 6.10.1-3 - libraries/prologue.txt should not have been ghosted From 0682b80a1daafbd841fbd83149b24ce5fe5de24b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 Nov 2008 02:52:10 +0000 Subject: [PATCH 068/530] - add cabal2spec and cabal-lib-template.spec for easy Cabal library packaging - simplify script macros: make ghc_preinst_script and ghc_postun_script no-ops and ghc_preun_script only unregister for uninstall --- Makefile | 2 +- cabal-lib-template.spec | 115 ++++++++++++++++++++++++++++++++++++++++ cabal2spec | 23 ++++++++ ghc-rpm-macros.ghc | 4 +- ghc.spec | 21 ++++++-- 5 files changed, 158 insertions(+), 7 deletions(-) create mode 100644 cabal-lib-template.spec create mode 100755 cabal2spec diff --git a/Makefile b/Makefile index d85df4e..e685c66 100644 --- a/Makefile +++ b/Makefile @@ -1,7 +1,7 @@ # Makefile for source rpm: ghc # $Id$ NAME := ghc -SPECFILE = $(firstword $(wildcard *.spec)) +SPECFILE = $(NAME).spec define find-makefile-common for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done diff --git a/cabal-lib-template.spec b/cabal-lib-template.spec new file mode 100644 index 0000000..9b396e6 --- /dev/null +++ b/cabal-lib-template.spec @@ -0,0 +1,115 @@ +%define pkg_name @PACKAGE@ +%define ghc_version @GHC_VERSION@ + +%define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{pkg_name}-%{version} +%define pkg_docdir %{_docdir}/ghc/libraries/%{pkg_name} + +%define build_prof 1 +%define build_doc 1 + +# ghc does not emit debug information +%define debug_package %{nil} + +Name: ghc-%{pkg_name} +Version: @VERSION@ +Release: 1%{?dist} +Summary: Haskell %{pkg_name} library *FIXME* + +Group: Development/Libraries +License: BSD +URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{pkg_name} +Source0: http://hackage.haskell.org/packages/archive/%{pkg_name}/%{version}/%{pkg_name}-%{version}.tar.gz +Provides: %{name}-devel = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +# ghc has only been bootstrapped on the following archs: +ExclusiveArch: i386 x86_64 ppc +BuildRequires: ghc = %{ghc_version} +%if %{build_prof} +BuildRequires: ghc-prof = %{ghc_version} +%endif +Requires: ghc = %{ghc_version} +Requires(post): ghc = %{ghc_version} +Requires(preun): ghc = %{ghc_version} +Requires(postun): ghc = %{ghc_version} + +%description +Haskell %{pkg_name} library for ghc-%{ghc_version}. *FIXME* + + +%if %{build_prof} +%package prof +Summary: Profiling libraries for %{name} +Group: Development/Libraries +Requires: ghc-prof = %{ghc_version} + +%description prof +This package contains profiling libraries for ghc %{ghc_version}. +%endif + + +%prep +%setup -q -n %{pkg_name}-%{version} + + +%build +%cabal_configure --ghc \ +%if %{build_prof} + -p +%else +%{nil} +%endif +%cabal_build +%if %{build_doc} +%cabal_haddock +%endif +%ghc_gen_scripts + + +%install +rm -rf $RPM_BUILD_ROOT +%cabal_install +%ghc_install_scripts +%ghc_gen_filelists %{name} + + +%clean +rm -rf $RPM_BUILD_ROOT + + +%post +%ghc_postinst_script +%if %{build_doc} +%ghc_reindex_haddock +%endif + + +%preun +%ghc_preun_script + + +%postun +if [ "$1" -eq 0 ] ; then +%if %{build_doc} + %ghc_reindex_haddock +%endif +fi + + +%files -f %{name}.files +%defattr(-,root,root,-) +%doc LICENSE README +%if %{build_doc} +%{pkg_docdir} +%endif + + +%if %{build_prof} +%files prof -f %{name}-prof.files +%defattr(-,root,root,-) +%doc LICENSE +%endif + + +%changelog +* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 +- initial packaging for Fedora diff --git a/cabal2spec b/cabal2spec new file mode 100755 index 0000000..dd6b542 --- /dev/null +++ b/cabal2spec @@ -0,0 +1,23 @@ +#!/bin/sh + +[ $# -ne 1 ] && echo "Usage: $0 lib-ver[.tar.gz]" && exit 1 + +INPUT=$1 + +case $INPUT in + */*) INPUT=$(basename $INPUT) ;; +esac + +INPUT=$(echo $INPUT | sed -e "s/.tar.gz//") + +VERSION=$(echo $INPUT | sed -e "s/[A-Za-z-]*-//") + +NAME=$(echo $INPUT | sed -e "s/-$VERSION//") + +[ -r ghc-$NAME.spec ] && echo "ghc-$NAME.spec already exists!" && exit 1 + +cp /usr/share/ghc/cabal-lib-template.spec ghc-$NAME.spec + +echo "created ghc-$NAME.spec" + +sed -i -e "s/@PACKAGE@/$NAME/" -e "s/@GHC_VERSION@/$(ghc --numeric-version)/" -e "s/@VERSION@/$VERSION/" -e "s/@DATE@/`date +\"%a %b %e %Y\"`/" ghc-$NAME.spec diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 599135d..8391596 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -40,7 +40,6 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ %{nil} %ghc_preinst_script \ -[ "$1" = 2 ] && %{pkg_libdir}/unregister.sh >&/dev/null || : \ %{nil} %ghc_postinst_script \ @@ -48,11 +47,10 @@ install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ %{nil} %ghc_preun_script \ -%{pkg_libdir}/unregister.sh >&/dev/null \ +[ "$1" = 0 ] && %{pkg_libdir}/unregister.sh >&/dev/null \ %{nil} %ghc_postun_script \ -[ "$1" = 1 ] && %{pkg_libdir}/register.sh >& /dev/null || : \ %{nil} %ghc_reindex_haddock \ diff --git a/ghc.spec b/ghc.spec index c93357e..34a1edc 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -25,6 +25,8 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc +Source3: cabal-lib-template.spec +Source4: cabal2spec URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel, libedit-devel Requires(post): policycoreutils @@ -67,7 +69,7 @@ Summary: Documentation for GHC Group: Development/Languages Requires: %{name} = %{version}-%{release} # for haddock -Requires(post): %{name} = %{version}-%{release} +Requires(posttrans): %{name} = %{version}-%{release} %description doc Preformatted documentation for the Glorious Glasgow Haskell @@ -126,7 +128,14 @@ make DESTDIR=${RPM_BUILD_ROOT} install-docs # install rpm macros mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc - + +# spec templating +# cabal-lib-template.spec +mkdir -p ${RPM_BUILD_ROOT}/%{_datadir}/ghc +cp -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_datadir}/ghc/ +# cabal2spec +install -m 0755 -p %{SOURCE4} ${RPM_BUILD_ROOT}/%{_bindir} + SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT @@ -192,6 +201,7 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf +%{_datadir}/ghc %if %{build_prof} %files prof -f rpm-prof-filelist @@ -217,6 +227,11 @@ fi %endif %changelog +* Tue Nov 25 2008 Jens Petersen - 6.10.1-5 +- add cabal2spec and cabal-lib-template.spec for easy Cabal library packaging +- simplify script macros: make ghc_preinst_script and ghc_postun_script no-ops + and ghc_preun_script only unregister for uninstall + * Tue Nov 11 2008 Jens Petersen - 6.10.1-4 - fix broken urls to haddock docs created by gen_contents_index script - avoid haddock errors when upgrading by making doc post script posttrans From 10d4eb08a11865e1ace6958e2c31fcfab0b886eb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 Nov 2008 03:47:45 +0000 Subject: [PATCH 069/530] omit README from lib spec template for now, since some hackage packages don't hav e one --- cabal-lib-template.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/cabal-lib-template.spec b/cabal-lib-template.spec index 9b396e6..fca146d 100644 --- a/cabal-lib-template.spec +++ b/cabal-lib-template.spec @@ -97,7 +97,7 @@ fi %files -f %{name}.files %defattr(-,root,root,-) -%doc LICENSE README +%doc LICENSE %if %{build_doc} %{pkg_docdir} %endif From b17255a6410f92efb0c965ee7ea13a0d7637a3af Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 Nov 2008 09:15:17 +0000 Subject: [PATCH 070/530] - add support for bin and binlib packages to cabal2spec script and only grep .cabal files for exposed-module/executable - output bin and/or lib status too --- cabal-bin-template.spec.in | 48 +++++++ cabal-binlib-template.spec.in | 122 ++++++++++++++++++ ...emplate.spec => cabal-lib-template.spec.in | 35 +++-- cabal2spec | 44 +++++-- ghc.spec | 16 ++- 5 files changed, 228 insertions(+), 37 deletions(-) create mode 100644 cabal-bin-template.spec.in create mode 100644 cabal-binlib-template.spec.in rename cabal-lib-template.spec => cabal-lib-template.spec.in (66%) diff --git a/cabal-bin-template.spec.in b/cabal-bin-template.spec.in new file mode 100644 index 0000000..acb26b0 --- /dev/null +++ b/cabal-bin-template.spec.in @@ -0,0 +1,48 @@ +# ghc does not emit debug information +%define debug_package %{nil} + +Name: @PACKAGE@ +Version: @VERSION@ +Release: 1%{?dist} +Summary: *FIXME* + +Group: *FIXME* +License: BSD? +URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} +Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +ExclusiveArch: i386 x86_64 ppc + +BuildRequires: ghc + +%description +*FIXME* + + +%prep +%setup -q + + +%build +%cabal_configure +%cabal_build + + +%install +rm -rf $RPM_BUILD_ROOT +%cabal_install + + +%clean +rm -rf $RPM_BUILD_ROOT + + +%files +%defattr(-,root,root,-) +%doc LICENSE +%{_bindir}/%{name} + + +%changelog +* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 +- initial packaging for Fedora created by cabal2spec diff --git a/cabal-binlib-template.spec.in b/cabal-binlib-template.spec.in new file mode 100644 index 0000000..d35d42c --- /dev/null +++ b/cabal-binlib-template.spec.in @@ -0,0 +1,122 @@ +%define ghc_version @GHC_VERSION@ + +%define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{name}-%{version} +%define pkg_docdir %{_docdir}/ghc/libraries/%{name} + +%define build_prof 1 +%define build_doc 1 + +# ghc does not emit debug information +%define debug_package %{nil} + +Name: @PACKAGE@ +Version: @VERSION@ +Release: 1%{?dist} +Summary: *FIXME* + +Group: *FIXME* +License: BSD? +URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} +Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz +Provides: %{name}-devel = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +# ghc has only been bootstrapped on the following archs: +ExclusiveArch: i386 x86_64 ppc +BuildRequires: ghc = %{ghc_version} +%if %{build_prof} +BuildRequires: ghc-prof = %{ghc_version} +%endif + +%description +*FIXME* + + +%package -n ghc-%{name} +Summary: Haskell %{name} library *FIXME* +Group: Development/Libraries +Provides: ghc-%{name}-devel = %{version}-%{release} +Requires: ghc = %{ghc_version} +Requires(post): ghc = %{ghc_version} +Requires(preun): ghc = %{ghc_version} +Requires(postun): ghc = %{ghc_version} + +%description -n ghc-%{name} +Haskell %{name} library for ghc-%{ghc_version}. *FIXME* + + +%if %{build_prof} +%package prof +Summary: Profiling libraries for ghc-%{name} +Group: Development/Libraries +Requires: ghc-prof = %{ghc_version} + +%description prof +This package contains profiling libraries for ghc %{ghc_version}. +%endif + + +%prep +%setup -q -n %{name}-%{version} + + +%build +%cabal_configure --ghc \ +%if %{build_prof} + -p +%else +%{nil} +%endif +%cabal_build +%if %{build_doc} +%cabal_haddock +%endif +%ghc_gen_scripts + + +%install +rm -rf $RPM_BUILD_ROOT +%cabal_install +%ghc_install_scripts +%ghc_gen_filelists %{name} + + +%clean +rm -rf $RPM_BUILD_ROOT + + +%post +%ghc_postinst_script +%if %{build_doc} +%ghc_reindex_haddock +%endif + + +%preun +%ghc_preun_script + + +%postun +if [ "$1" -eq 0 ] ; then +%if %{build_doc} + %ghc_reindex_haddock +%endif +fi + + +%files -f %{name}.files +%defattr(-,root,root,-) +%doc LICENSE +%if %{build_doc} +%{pkg_docdir} +%endif + + +%if %{build_prof} +%files prof -f %{name}-prof.files +%defattr(-,root,root,-) +%endif + + +%changelog +* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 +- initial packaging for Fedora created by cabal2spec diff --git a/cabal-lib-template.spec b/cabal-lib-template.spec.in similarity index 66% rename from cabal-lib-template.spec rename to cabal-lib-template.spec.in index fca146d..4d4f58e 100644 --- a/cabal-lib-template.spec +++ b/cabal-lib-template.spec.in @@ -10,25 +10,25 @@ # ghc does not emit debug information %define debug_package %{nil} -Name: ghc-%{pkg_name} -Version: @VERSION@ -Release: 1%{?dist} -Summary: Haskell %{pkg_name} library *FIXME* - -Group: Development/Libraries -License: BSD -URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{pkg_name} -Source0: http://hackage.haskell.org/packages/archive/%{pkg_name}/%{version}/%{pkg_name}-%{version}.tar.gz -Provides: %{name}-devel = %{version}-%{release} -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +Name: ghc-%{pkg_name} +Version: @VERSION@ +Release: 1%{?dist} +Summary: Haskell %{pkg_name} library *FIXME* + +Group: Development/Libraries +License: BSD? +URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{pkg_name} +Source0: http://hackage.haskell.org/packages/archive/%{pkg_name}/%{version}/%{pkg_name}-%{version}.tar.gz +Provides: %{name}-devel = %{version}-%{release} +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # ghc has only been bootstrapped on the following archs: -ExclusiveArch: i386 x86_64 ppc -BuildRequires: ghc = %{ghc_version} +ExclusiveArch: i386 x86_64 ppc +BuildRequires: ghc = %{ghc_version} %if %{build_prof} -BuildRequires: ghc-prof = %{ghc_version} +BuildRequires: ghc-prof = %{ghc_version} %endif -Requires: ghc = %{ghc_version} -Requires(post): ghc = %{ghc_version} +Requires: ghc = %{ghc_version} +Requires(post): ghc = %{ghc_version} Requires(preun): ghc = %{ghc_version} Requires(postun): ghc = %{ghc_version} @@ -106,10 +106,9 @@ fi %if %{build_prof} %files prof -f %{name}-prof.files %defattr(-,root,root,-) -%doc LICENSE %endif %changelog * @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 -- initial packaging for Fedora +- initial packaging for Fedora created by cabal2spec diff --git a/cabal2spec b/cabal2spec index dd6b542..d16978b 100755 --- a/cabal2spec +++ b/cabal2spec @@ -1,23 +1,43 @@ #!/bin/sh -[ $# -ne 1 ] && echo "Usage: $0 lib-ver[.tar.gz]" && exit 1 +set -e -INPUT=$1 +[ $# -ne 1 -o ! -r $1 ] && echo "Usage: $0 hackage-version.tar.gz" && exit 1 -case $INPUT in - */*) INPUT=$(basename $INPUT) ;; -esac +HACKAGE=$1 -INPUT=$(echo $INPUT | sed -e "s/.tar.gz//") - -VERSION=$(echo $INPUT | sed -e "s/[A-Za-z-]*-//") +INPUT=$(basename $HACKAGE .tar.gz) +VERSION=$(echo $INPUT | sed -e "s/.*-//") NAME=$(echo $INPUT | sed -e "s/-$VERSION//") -[ -r ghc-$NAME.spec ] && echo "ghc-$NAME.spec already exists!" && exit 1 +TMPDIR=$(mktemp -d) +CURRENT_DIR=$PWD +cd $TMPDIR +tar zxf $HACKAGE "*.cabal" + +if grep -qi exposed-modules: */*.cabal; then + HAS_LIB=yes +fi + +if grep -qi executable */*.cabal; then + HAS_BIN=yes +fi +cd - +rm -rf $TMPDIR + +if [ "$HAS_LIB" -a ! "$HAS_BIN" ]; then + PREFIX=ghc- +fi + +SPECFILE=$PREFIX$NAME.spec + +[ -r $SPECFILE ] && echo "$SPECFILE already exists!" && exit 1 + +cp /usr/share/ghc/cabal-${HAS_BIN:+bin}${HAS_LIB:+lib}-template.spec.in $SPECFILE -cp /usr/share/ghc/cabal-lib-template.spec ghc-$NAME.spec +echo "created $SPECFILE (${HAS_BIN:+bin}${HAS_LIB:+lib})" -echo "created ghc-$NAME.spec" +DATE=$(env LANG=C date +"%a %b %e %Y") -sed -i -e "s/@PACKAGE@/$NAME/" -e "s/@GHC_VERSION@/$(ghc --numeric-version)/" -e "s/@VERSION@/$VERSION/" -e "s/@DATE@/`date +\"%a %b %e %Y\"`/" ghc-$NAME.spec +sed -i -e "s/@PACKAGE@/$NAME/" -e "s/@GHC_VERSION@/$(ghc --numeric-version)/" -e "s/@VERSION@/$VERSION/" -e "s/@DATE@/$DATE/" $SPECFILE diff --git a/ghc.spec b/ghc.spec index 34a1edc..84a489c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -25,8 +25,10 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc -Source3: cabal-lib-template.spec -Source4: cabal2spec +Source3: cabal2spec +Source4: cabal-bin-template.spec.in +Source5: cabal-lib-template.spec.in +Source6: cabal-binlib-template.spec.in URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel, libedit-devel Requires(post): policycoreutils @@ -130,11 +132,11 @@ mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc # spec templating -# cabal-lib-template.spec -mkdir -p ${RPM_BUILD_ROOT}/%{_datadir}/ghc -cp -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_datadir}/ghc/ # cabal2spec -install -m 0755 -p %{SOURCE4} ${RPM_BUILD_ROOT}/%{_bindir} +install -m 0755 -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_bindir} +# templates for bin, lib and binlib cabal hackages +mkdir -p ${RPM_BUILD_ROOT}/%{_datadir}/ghc +cp -p %{SOURCE4} %{SOURCE5} %{SOURCE6} ${RPM_BUILD_ROOT}/%{_datadir}/ghc/ SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files @@ -228,7 +230,7 @@ fi %changelog * Tue Nov 25 2008 Jens Petersen - 6.10.1-5 -- add cabal2spec and cabal-lib-template.spec for easy Cabal library packaging +- add cabal2spec and template files for easy cabal hackage packaging - simplify script macros: make ghc_preinst_script and ghc_postun_script no-ops and ghc_preun_script only unregister for uninstall From 9c2030439c9a188f056bb5523c8ed871d7f9f794 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 Nov 2008 15:40:11 +0000 Subject: [PATCH 071/530] quote some test args --- cabal2spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/cabal2spec b/cabal2spec index d16978b..ab68656 100755 --- a/cabal2spec +++ b/cabal2spec @@ -2,7 +2,7 @@ set -e -[ $# -ne 1 -o ! -r $1 ] && echo "Usage: $0 hackage-version.tar.gz" && exit 1 +[ $# -ne 1 -o ! -r "$1" ] && echo "Usage: $0 hackage-version.tar.gz" && exit 1 HACKAGE=$1 @@ -32,7 +32,7 @@ fi SPECFILE=$PREFIX$NAME.spec -[ -r $SPECFILE ] && echo "$SPECFILE already exists!" && exit 1 +[ -r "$SPECFILE" ] && echo "$SPECFILE already exists!" && exit 1 cp /usr/share/ghc/cabal-${HAS_BIN:+bin}${HAS_LIB:+lib}-template.spec.in $SPECFILE From 74a3f2521e07b455f7cab3e4a4389cd75c4de0a4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 28 Nov 2008 02:47:49 +0000 Subject: [PATCH 072/530] - make cabal2spec work on .cabal files too, and read and check name and version from .cabal --- cabal2spec | 48 +++++++++++++++++++++++++++++++++--------------- ghc.spec | 4 ++++ 2 files changed, 37 insertions(+), 15 deletions(-) diff --git a/cabal2spec b/cabal2spec index ab68656..47b74db 100755 --- a/cabal2spec +++ b/cabal2spec @@ -2,29 +2,47 @@ set -e -[ $# -ne 1 -o ! -r "$1" ] && echo "Usage: $0 hackage-version.tar.gz" && exit 1 - -HACKAGE=$1 +[ $# -ne 1 -o ! -r "$1" ] && echo "Usage: $(basename $0) [hackage.tar.gz|hackage.cabal]" && exit 1 + +FILE=$1 + +case $FILE in + *.tar.gz) + TARNAME_VER=$(basename $FILE .tar.gz) + TARVERSION=$(echo $TARNAME_VER | sed -e "s/.*-//") + TARNAME=$(echo $TARNAME_VER | sed -e "s/-$TARVERSION//") + WORKDIR=$(mktemp -d) + tar zxf $FILE -C $WORKDIR "*.cabal" + CABAL="$WORKDIR/*/*.cabal" ;; + *.cabal) + CABAL=$FILE ;; +esac + +NAME=$(grep -i ^name: $CABAL | sed -e "s/[Nn]ame:[ \t]*//") +if [ -n "$TARNAME" -a "$TARNAME" != "$NAME" ]; then + echo "Warning: tarball name ($TARNAME) and cabal name ($NAME) differ!" +fi -INPUT=$(basename $HACKAGE .tar.gz) +VERSION=$(grep -i ^version: $CABAL | sed -e "s/[Vv]ersion:[ \t]*//") +if [ -n "$TARVERSION" -a "$TARVERSION" != "$VERSION" ]; then + echo "Warning: tarball version ($TARVERSION) and cabal version ($VERSION) differ!" +fi -VERSION=$(echo $INPUT | sed -e "s/.*-//") -NAME=$(echo $INPUT | sed -e "s/-$VERSION//") +CABALFILENAME=$(basename $CABAL .cabal) +if [ "$CABALFILENAME" != "$NAME" ]; then + echo "Warning: .cabal filename ($CABALFILENAME) and cabal Name field ($NAME) differ!" +fi -TMPDIR=$(mktemp -d) -CURRENT_DIR=$PWD -cd $TMPDIR -tar zxf $HACKAGE "*.cabal" -if grep -qi exposed-modules: */*.cabal; then +if grep -qi exposed-modules: $CABAL; then HAS_LIB=yes fi -if grep -qi executable */*.cabal; then +if grep -qi executable $CABAL; then HAS_BIN=yes fi -cd - -rm -rf $TMPDIR + +[ -d "$WORKDIR" ] && rm -r $WORKDIR if [ "$HAS_LIB" -a ! "$HAS_BIN" ]; then PREFIX=ghc- @@ -36,7 +54,7 @@ SPECFILE=$PREFIX$NAME.spec cp /usr/share/ghc/cabal-${HAS_BIN:+bin}${HAS_LIB:+lib}-template.spec.in $SPECFILE -echo "created $SPECFILE (${HAS_BIN:+bin}${HAS_LIB:+lib})" +echo "created $SPECFILE (${HAS_BIN:+bin}${HAS_LIB:+lib}) for $NAME-$VERSION" DATE=$(env LANG=C date +"%a %b %e %Y") diff --git a/ghc.spec b/ghc.spec index 84a489c..ba02fae 100644 --- a/ghc.spec +++ b/ghc.spec @@ -229,6 +229,10 @@ fi %endif %changelog +* Fri Nov 28 2008 Jens Petersen +- make cabal2spec work on .cabal files too, and + read and check name and version from .cabal + * Tue Nov 25 2008 Jens Petersen - 6.10.1-5 - add cabal2spec and template files for easy cabal hackage packaging - simplify script macros: make ghc_preinst_script and ghc_postun_script no-ops From ad8913e5ffd3e2bcb04de0ad133ab6d7a68c4fe0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 1 Dec 2008 05:46:36 +0000 Subject: [PATCH 073/530] - update macros.ghc to latest proposed revised packaging guidelines: - use runghc - drop trivial cabal_build and cabal_haddock macros - ghc_register_pkg and ghc_unregister_pkg replace ghc_preinst_script, ghc_postinst_script, ghc_preun_script, and ghc_postun_script - lib templates' prof subpackage requires main library again - make cabal2spec work on .cabal files too, and read and check name and version directly from .cabal file - ghc-prof does not need to own libraries/ dirs owned by main package --- cabal-bin-template.spec.in | 2 +- cabal-binlib-template.spec.in | 11 +++++---- cabal-lib-template.spec.in | 11 +++++---- ghc-rpm-macros.ghc | 45 +++++++---------------------------- ghc.spec | 15 ++++++++---- 5 files changed, 35 insertions(+), 49 deletions(-) diff --git a/cabal-bin-template.spec.in b/cabal-bin-template.spec.in index acb26b0..a69f081 100644 --- a/cabal-bin-template.spec.in +++ b/cabal-bin-template.spec.in @@ -25,7 +25,7 @@ BuildRequires: ghc %build %cabal_configure -%cabal_build +%cabal build %install diff --git a/cabal-binlib-template.spec.in b/cabal-binlib-template.spec.in index d35d42c..a91531c 100644 --- a/cabal-binlib-template.spec.in +++ b/cabal-binlib-template.spec.in @@ -48,6 +48,7 @@ Haskell %{name} library for ghc-%{ghc_version}. *FIXME* %package prof Summary: Profiling libraries for ghc-%{name} Group: Development/Libraries +Requires: ghc-%{name} = %{version}-%{release} Requires: ghc-prof = %{ghc_version} %description prof @@ -66,9 +67,9 @@ This package contains profiling libraries for ghc %{ghc_version}. %else %{nil} %endif -%cabal_build +%cabal build %if %{build_doc} -%cabal_haddock +%cabal haddock %endif %ghc_gen_scripts @@ -85,14 +86,16 @@ rm -rf $RPM_BUILD_ROOT %post -%ghc_postinst_script +%ghc_register_pkg %if %{build_doc} %ghc_reindex_haddock %endif %preun -%ghc_preun_script +if [ "$1" -eq 0 ] ; then + %ghc_unregister_pkg +fi %postun diff --git a/cabal-lib-template.spec.in b/cabal-lib-template.spec.in index 4d4f58e..9c587a2 100644 --- a/cabal-lib-template.spec.in +++ b/cabal-lib-template.spec.in @@ -40,6 +40,7 @@ Haskell %{pkg_name} library for ghc-%{ghc_version}. *FIXME* %package prof Summary: Profiling libraries for %{name} Group: Development/Libraries +Requires: %{name} = %{version}-%{release} Requires: ghc-prof = %{ghc_version} %description prof @@ -58,9 +59,9 @@ This package contains profiling libraries for ghc %{ghc_version}. %else %{nil} %endif -%cabal_build +%cabal build %if %{build_doc} -%cabal_haddock +%cabal haddock %endif %ghc_gen_scripts @@ -77,14 +78,16 @@ rm -rf $RPM_BUILD_ROOT %post -%ghc_postinst_script +%ghc_register_pkg %if %{build_doc} %ghc_reindex_haddock %endif %preun -%ghc_preun_script +if [ "$1" -eq 0 ] ; then + %ghc_unregister_pkg +fi %postun diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 8391596..75cf2ef 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,58 +1,31 @@ -%cabal %{_bindir}/runhaskell Setup +%cabal %{_bindir}/runghc Setup %cabal_configure \ %cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{pkg_docdir} --libsubdir='$compiler/$pkgid' -%cabal_build \ -%cabal build \ -%{nil} - %cabal_makefile \ %cabal makefile -f cabal-rpm.mk \ make -f cabal-rpm.mk %{_smp_mflags} \ %{nil} -%cabal_haddock \ -%cabal haddock \ -%{nil} - -%cabal_install \ -%cabal copy --destdir=${RPM_BUILD_ROOT} -v \ -%{nil} +%cabal_install %cabal copy --destdir=${RPM_BUILD_ROOT} -v %ghc_gen_filelists() \ rm -f %1.files %1-prof.files \ -echo '%defattr(-,root,root,-)' > %1-prof.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ echo '%defattr(-,root,root,-)' > %1.files \ find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1.files \ find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1.files \ +echo '%defattr(-,root,root,-)' > %1-prof.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1.files %1-prof.files \ %{nil} -%ghc_gen_scripts \ -%cabal register --gen-script \ -%cabal unregister --gen-script \ -%{nil} +%ghc_gen_scripts %cabal register --gen-script ; %cabal unregister --gen-script -%ghc_install_scripts \ -install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} \ -%{nil} +%ghc_install_scripts install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} -%ghc_preinst_script \ -%{nil} +%ghc_register_pkg %{pkg_libdir}/register.sh >/dev/null -%ghc_postinst_script \ -%{pkg_libdir}/register.sh >&/dev/null \ -%{nil} +%ghc_unregister_pkg %{pkg_libdir}/unregister.sh >/dev/null -%ghc_preun_script \ -[ "$1" = 0 ] && %{pkg_libdir}/unregister.sh >&/dev/null \ -%{nil} - -%ghc_postun_script \ -%{nil} - -%ghc_reindex_haddock \ -( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : \ -%{nil} +%ghc_reindex_haddock ( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : diff --git a/ghc.spec b/ghc.spec index ba02fae..73c885a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -150,7 +150,7 @@ sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files cat rpm-dir.files rpm-lib.files > rpm-base-filelist %if %{build_prof} -cat rpm-dir.files rpm-prof.files > rpm-prof-filelist +cat rpm-prof.files > rpm-prof-filelist %endif # these are handled as alternatives @@ -229,9 +229,16 @@ fi %endif %changelog -* Fri Nov 28 2008 Jens Petersen +* Mon Dec 1 2008 Jens Petersen - 6.10.1-6 +- update macros.ghc to latest proposed revised packaging guidelines: + - use runghc + - drop trivial cabal_build and cabal_haddock + - ghc_register_pkg and ghc_unregister_pkg replace ghc_preinst_script, + ghc_postinst_script, ghc_preun_script, and ghc_postun_script +- library templates prof subpackage requires main library again - make cabal2spec work on .cabal files too, and - read and check name and version from .cabal + read and check name and version directly from .cabal file +- ghc-prof does not need to own libraries dirs owned by main package * Tue Nov 25 2008 Jens Petersen - 6.10.1-5 - add cabal2spec and template files for easy cabal hackage packaging From 18d2312b751f5a38d039e27005a31f18ed60cd49 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 1 Dec 2008 05:49:24 +0000 Subject: [PATCH 074/530] tweak changelog --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 73c885a..b1ad624 100644 --- a/ghc.spec +++ b/ghc.spec @@ -232,7 +232,7 @@ fi * Mon Dec 1 2008 Jens Petersen - 6.10.1-6 - update macros.ghc to latest proposed revised packaging guidelines: - use runghc - - drop trivial cabal_build and cabal_haddock + - drop trivial cabal_build and cabal_haddock macros - ghc_register_pkg and ghc_unregister_pkg replace ghc_preinst_script, ghc_postinst_script, ghc_preun_script, and ghc_postun_script - library templates prof subpackage requires main library again From 644d44d68238b0e1c9b9aaebf3057614a9934cf7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Dec 2008 09:50:10 +0000 Subject: [PATCH 075/530] more template fixes: - version pkg_docdir - put provides in lib subsubpackage - binlib scripts are for lib subpackage --- cabal-binlib-template.spec.in | 32 +++++++++++++++++--------------- cabal-lib-template.spec.in | 4 ++-- ghc.spec | 6 ++++++ 3 files changed, 25 insertions(+), 17 deletions(-) diff --git a/cabal-binlib-template.spec.in b/cabal-binlib-template.spec.in index a91531c..47c4ffb 100644 --- a/cabal-binlib-template.spec.in +++ b/cabal-binlib-template.spec.in @@ -1,7 +1,7 @@ %define ghc_version @GHC_VERSION@ %define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{name}-%{version} -%define pkg_docdir %{_docdir}/ghc/libraries/%{name} +%define pkg_docdir %{_docdir}/ghc/libraries/%{name}-%{version} %define build_prof 1 %define build_doc 1 @@ -18,7 +18,6 @@ Group: *FIXME* License: BSD? URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz -Provides: %{name}-devel = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # ghc has only been bootstrapped on the following archs: ExclusiveArch: i386 x86_64 ppc @@ -41,23 +40,23 @@ Requires(preun): ghc = %{ghc_version} Requires(postun): ghc = %{ghc_version} %description -n ghc-%{name} -Haskell %{name} library for ghc-%{ghc_version}. *FIXME* +Haskell %{name} library. *FIXME* %if %{build_prof} -%package prof -Summary: Profiling libraries for ghc-%{name} +%package -n ghc-%{name}-prof +Summary: Profiling libraries for %{name} Group: Development/Libraries Requires: ghc-%{name} = %{version}-%{release} Requires: ghc-prof = %{ghc_version} -%description prof -This package contains profiling libraries for ghc %{ghc_version}. +%description -n ghc-%{name}-prof +This package contains profiling libraries for %{name}. %endif %prep -%setup -q -n %{name}-%{version} +%setup -q %build @@ -78,44 +77,47 @@ This package contains profiling libraries for ghc %{ghc_version}. rm -rf $RPM_BUILD_ROOT %cabal_install %ghc_install_scripts -%ghc_gen_filelists %{name} +%ghc_gen_filelists ghc-%{name} %clean rm -rf $RPM_BUILD_ROOT -%post +%post -n ghc-%{name} %ghc_register_pkg %if %{build_doc} %ghc_reindex_haddock %endif -%preun +%preun -n ghc-%{name} if [ "$1" -eq 0 ] ; then %ghc_unregister_pkg fi -%postun +%postun -n ghc-%{name} if [ "$1" -eq 0 ] ; then %if %{build_doc} %ghc_reindex_haddock %endif fi - -%files -f %{name}.files +%files %defattr(-,root,root,-) %doc LICENSE +%{_bindir}/%{name} + +%files -n ghc-%{name} -f ghc-%{name}.files +%defattr(-,root,root,-) %if %{build_doc} %{pkg_docdir} %endif %if %{build_prof} -%files prof -f %{name}-prof.files +%files -n ghc-%{name}-prof -f ghc-%{name}-prof.files %defattr(-,root,root,-) %endif diff --git a/cabal-lib-template.spec.in b/cabal-lib-template.spec.in index 9c587a2..fbe2645 100644 --- a/cabal-lib-template.spec.in +++ b/cabal-lib-template.spec.in @@ -2,7 +2,7 @@ %define ghc_version @GHC_VERSION@ %define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{pkg_name}-%{version} -%define pkg_docdir %{_docdir}/ghc/libraries/%{pkg_name} +%define pkg_docdir %{_docdir}/ghc/libraries/%{pkg_name}-%{version} %define build_prof 1 %define build_doc 1 @@ -44,7 +44,7 @@ Requires: %{name} = %{version}-%{release} Requires: ghc-prof = %{ghc_version} %description prof -This package contains profiling libraries for ghc %{ghc_version}. +This package contains profiling libraries for %{name}. %endif diff --git a/ghc.spec b/ghc.spec index b1ad624..6829daf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -229,6 +229,12 @@ fi %endif %changelog +* Fri Dec 5 2008 Jens Petersen +- more template fixes: + - version pkg_docdir + - put provides in lib subsubpackage + - binlib scripts are for lib subpackage + * Mon Dec 1 2008 Jens Petersen - 6.10.1-6 - update macros.ghc to latest proposed revised packaging guidelines: - use runghc From 65d3718c162a990876538a4c1f7c968ccf585734 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 19 Jan 2009 05:39:55 +0000 Subject: [PATCH 076/530] - move spec templates to haskell-packaging for easy updating - provide correct haddock version spec templating: - use bcond for - add doc subpackages to lib and binlib templates - add license header for cabal2spec --- cabal-binlib-template.spec.in | 53 +++++++++++++++++++++------------ cabal-lib-template.spec.in | 56 ++++++++++++++++++++++------------- ghc.spec | 22 +++----------- 3 files changed, 73 insertions(+), 58 deletions(-) diff --git a/cabal-binlib-template.spec.in b/cabal-binlib-template.spec.in index 47c4ffb..9fc7e2e 100644 --- a/cabal-binlib-template.spec.in +++ b/cabal-binlib-template.spec.in @@ -3,8 +3,8 @@ %define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{name}-%{version} %define pkg_docdir %{_docdir}/ghc/libraries/%{name}-%{version} -%define build_prof 1 -%define build_doc 1 +%bcond_without prof +%bcond_without doc # ghc does not emit debug information %define debug_package %{nil} @@ -15,14 +15,14 @@ Release: 1%{?dist} Summary: *FIXME* Group: *FIXME* -License: BSD? +License: BSD? *FIXME* URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # ghc has only been bootstrapped on the following archs: ExclusiveArch: i386 x86_64 ppc BuildRequires: ghc = %{ghc_version} -%if %{build_prof} +%if %{with prof} BuildRequires: ghc-prof = %{ghc_version} %endif @@ -37,13 +37,24 @@ Provides: ghc-%{name}-devel = %{version}-%{release} Requires: ghc = %{ghc_version} Requires(post): ghc = %{ghc_version} Requires(preun): ghc = %{ghc_version} -Requires(postun): ghc = %{ghc_version} %description -n ghc-%{name} Haskell %{name} library. *FIXME* -%if %{build_prof} +%if %{with doc} +%package -n ghc-%{name}-doc +Summary: Documentation for %{name} +Group: Development/Libraries +Requires: ghc-doc = %{ghc_version} +Requires(postun): ghc-doc = %{ghc_version} + +%description -n ghc-%{name}-doc +This package contains development documentation files for the %{name} library. +%endif + + +%if %{with prof} %package -n ghc-%{name}-prof Summary: Profiling libraries for %{name} Group: Development/Libraries @@ -60,14 +71,9 @@ This package contains profiling libraries for %{name}. %build -%cabal_configure --ghc \ -%if %{build_prof} - -p -%else -%{nil} -%endif +%cabal_configure --ghc %{!?without_prof:-p} %cabal build -%if %{build_doc} +%if %{with doc} %cabal haddock %endif %ghc_gen_scripts @@ -86,7 +92,10 @@ rm -rf $RPM_BUILD_ROOT %post -n ghc-%{name} %ghc_register_pkg -%if %{build_doc} + + +%if %{with doc} +%post -n ghc-%{name}-doc %ghc_reindex_haddock %endif @@ -97,26 +106,32 @@ if [ "$1" -eq 0 ] ; then fi -%postun -n ghc-%{name} +%if %{with doc} +%postun -n ghc-%{name}-doc if [ "$1" -eq 0 ] ; then -%if %{build_doc} %ghc_reindex_haddock -%endif fi +%endif + %files %defattr(-,root,root,-) %doc LICENSE %{_bindir}/%{name} + %files -n ghc-%{name} -f ghc-%{name}.files %defattr(-,root,root,-) -%if %{build_doc} + + +%if %{with doc} +%files -n ghc-%{name}-doc +%defattr(-,root,root,-) %{pkg_docdir} %endif -%if %{build_prof} +%if %{with prof} %files -n ghc-%{name}-prof -f ghc-%{name}-prof.files %defattr(-,root,root,-) %endif diff --git a/cabal-lib-template.spec.in b/cabal-lib-template.spec.in index fbe2645..c8d6440 100644 --- a/cabal-lib-template.spec.in +++ b/cabal-lib-template.spec.in @@ -4,8 +4,8 @@ %define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{pkg_name}-%{version} %define pkg_docdir %{_docdir}/ghc/libraries/%{pkg_name}-%{version} -%define build_prof 1 -%define build_doc 1 +%bcond_without prof +%bcond_without doc # ghc does not emit debug information %define debug_package %{nil} @@ -16,27 +16,39 @@ Release: 1%{?dist} Summary: Haskell %{pkg_name} library *FIXME* Group: Development/Libraries -License: BSD? +License: BSD? *FIXME* URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{pkg_name} Source0: http://hackage.haskell.org/packages/archive/%{pkg_name}/%{version}/%{pkg_name}-%{version}.tar.gz -Provides: %{name}-devel = %{version}-%{release} BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) + +Provides: %{name}-devel = %{version}-%{release} # ghc has only been bootstrapped on the following archs: ExclusiveArch: i386 x86_64 ppc BuildRequires: ghc = %{ghc_version} -%if %{build_prof} +%if %{with prof} BuildRequires: ghc-prof = %{ghc_version} %endif Requires: ghc = %{ghc_version} Requires(post): ghc = %{ghc_version} Requires(preun): ghc = %{ghc_version} -Requires(postun): ghc = %{ghc_version} %description Haskell %{pkg_name} library for ghc-%{ghc_version}. *FIXME* -%if %{build_prof} +%if %{with doc} +%package doc +Summary: Documentation for %{name} +Group: Development/Libraries +Requires: ghc-doc = %{ghc_version} +Requires(postun): ghc-doc = %{ghc_version} + +%description doc +This package contains development documentation files for the %{name} library. +%endif + + +%if %{with prof} %package prof Summary: Profiling libraries for %{name} Group: Development/Libraries @@ -53,14 +65,9 @@ This package contains profiling libraries for %{name}. %build -%cabal_configure --ghc \ -%if %{build_prof} - -p -%else -%{nil} -%endif +%cabal_configure --ghc %{!?without_prof:-p} %cabal build -%if %{build_doc} +%if %{with doc} %cabal haddock %endif %ghc_gen_scripts @@ -77,9 +84,12 @@ rm -rf $RPM_BUILD_ROOT rm -rf $RPM_BUILD_ROOT -%post +%post %ghc_register_pkg -%if %{build_doc} + + +%if %{with doc} +%post doc %ghc_reindex_haddock %endif @@ -90,23 +100,27 @@ if [ "$1" -eq 0 ] ; then fi -%postun +%if %{with doc} +%postun doc if [ "$1" -eq 0 ] ; then -%if %{build_doc} %ghc_reindex_haddock -%endif fi +%endif %files -f %{name}.files %defattr(-,root,root,-) %doc LICENSE -%if %{build_doc} + + +%if %{with doc} +%files doc +%defattr(-,root,root,-) %{pkg_docdir} %endif -%if %{build_prof} +%if %{with prof} %files prof -f %{name}-prof.files %defattr(-,root,root,-) %endif diff --git a/ghc.spec b/ghc.spec index 6829daf..6328d3b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -25,17 +25,13 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc -Source3: cabal2spec -Source4: cabal-bin-template.spec.in -Source5: cabal-lib-template.spec.in -Source6: cabal-binlib-template.spec.in URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel, libedit-devel Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 # introduced for f11 and to be removed for f13: -Provides: haddock = 2.2.2 +Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel %if %{build_doc} @@ -131,13 +127,6 @@ make DESTDIR=${RPM_BUILD_ROOT} install-docs mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc -# spec templating -# cabal2spec -install -m 0755 -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_bindir} -# templates for bin, lib and binlib cabal hackages -mkdir -p ${RPM_BUILD_ROOT}/%{_datadir}/ghc -cp -p %{SOURCE4} %{SOURCE5} %{SOURCE6} ${RPM_BUILD_ROOT}/%{_datadir}/ghc/ - SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files ( cd $RPM_BUILD_ROOT @@ -203,7 +192,6 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%{_datadir}/ghc %if %{build_prof} %files prof -f rpm-prof-filelist @@ -229,11 +217,9 @@ fi %endif %changelog -* Fri Dec 5 2008 Jens Petersen -- more template fixes: - - version pkg_docdir - - put provides in lib subsubpackage - - binlib scripts are for lib subpackage +* Mon Jan 19 2009 Jens Petersen - 6.10.1-6 +- move spec templates to a haskell-packaging for easy updating +- provide correct haddock version * Mon Dec 1 2008 Jens Petersen - 6.10.1-6 - update macros.ghc to latest proposed revised packaging guidelines: From e74c4291aa6b8221c953d0026b645068a2c88d2d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 19 Jan 2009 05:47:00 +0000 Subject: [PATCH 077/530] bump release --- cabal2spec | 17 +++++++++++++++++ ghc.spec | 4 ++-- 2 files changed, 19 insertions(+), 2 deletions(-) diff --git a/cabal2spec b/cabal2spec index 47b74db..f1b9df2 100755 --- a/cabal2spec +++ b/cabal2spec @@ -1,5 +1,22 @@ #!/bin/sh +# Copyright (C) 2008-2009 Red Hat, Inc +# Written by Jens Petersen , 2008. +# +# This program is free software; you can redistribute it and/or modify +# it under the terms of the GNU General Public License as published by +# the Free Software Foundation; either version 2, or (at your option) +# any later version. +# +# This program is distributed in the hope that it will be useful, +# but WITHOUT ANY WARRANTY; without even the implied warranty of +# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +# GNU General Public License for more details. +# +# You should have received a copy of the GNU General Public License +# along with this program; if not, write to the Free Software Foundation, +# Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. + set -e [ $# -ne 1 -o ! -r "$1" ] && echo "Usage: $(basename $0) [hackage.tar.gz|hackage.cabal]" && exit 1 diff --git a/ghc.spec b/ghc.spec index 6328d3b..17b9d5d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 6%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -217,7 +217,7 @@ fi %endif %changelog -* Mon Jan 19 2009 Jens Petersen - 6.10.1-6 +* Mon Jan 19 2009 Jens Petersen - 6.10.1-7 - move spec templates to a haskell-packaging for easy updating - provide correct haddock version From 001d3451a62055b316e01bb9a039925a46c853cf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 19 Jan 2009 10:58:49 +0000 Subject: [PATCH 078/530] buildrequire ncurses-devel to fix build of missing editline package needed for ghci line-editing (#478466) --- ghc.spec | 4 ++++ 1 file changed, 4 insertions(+) diff --git a/ghc.spec b/ghc.spec index 17b9d5d..428ba78 100644 --- a/ghc.spec +++ b/ghc.spec @@ -34,6 +34,8 @@ Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel +# editline package requires ncurses to configure +BuildRequires: ncurses-devel %if %{build_doc} BuildRequires: libxslt, docbook-style-xsl %endif @@ -218,6 +220,8 @@ fi %changelog * Mon Jan 19 2009 Jens Petersen - 6.10.1-7 +- buildrequire ncurses-devel to fix build of missing editline package needed + for ghci line-editing (#478466) - move spec templates to a haskell-packaging for easy updating - provide correct haddock version From 1acf5c7d024faef623235ba0602453b20afd8563 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 23 Jan 2009 07:24:23 +0000 Subject: [PATCH 079/530] fix to libedit means can drop BR ncurses-devel workaround (#481252) --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 428ba78..350e620 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -34,8 +34,6 @@ Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel -# editline package requires ncurses to configure -BuildRequires: ncurses-devel %if %{build_doc} BuildRequires: libxslt, docbook-style-xsl %endif @@ -219,6 +217,9 @@ fi %endif %changelog +* Fri Jan 23 2009 Jens Petersen - 6.10.1-8 +- fix to libedit means can drop ncurses-devel BR workaround (#481252) + * Mon Jan 19 2009 Jens Petersen - 6.10.1-7 - buildrequire ncurses-devel to fix build of missing editline package needed for ghci line-editing (#478466) @@ -252,7 +253,7 @@ fi - Fix a minor packaging glitch * Tue Nov 04 2008 Bryan O'Sullivan - 6.10.1-1 -- Update to 6.10.1 in observance of President Obama +- Update to 6.10.1 * Thu Oct 23 2008 Jens Petersen - 6.10.0.20081007-9 - remove redundant --haddockdir from cabal_configure From 0eea3c51b51ff52a0882c508bffd20598bb5dec4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 10 Feb 2009 08:15:40 +0000 Subject: [PATCH 080/530] - require and buildrequire libedit-devel > 2.11-2 - move top doc dirs to main package for better sharing - move gen_contents_index and ghost index files to main package - protect ghc_register_pkg and ghc_unregister_pkg --- ghc-rpm-macros.ghc | 4 ++-- ghc.spec | 35 +++++++++++++++++++++-------------- 2 files changed, 23 insertions(+), 16 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 75cf2ef..b38f658 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -24,8 +24,8 @@ sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1.files %1-prof.files \ %ghc_install_scripts install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} -%ghc_register_pkg %{pkg_libdir}/register.sh >/dev/null +%ghc_register_pkg %{pkg_libdir}/register.sh >/dev/null || : -%ghc_unregister_pkg %{pkg_libdir}/unregister.sh >/dev/null +%ghc_unregister_pkg %{pkg_libdir}/unregister.sh >/dev/null || : %ghc_reindex_haddock ( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : diff --git a/ghc.spec b/ghc.spec index 350e620..bedc328 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compilation system # See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 ExcludeArch: alpha ppc64 @@ -26,14 +26,15 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc URL: http://haskell.org/ghc/ -Requires: gcc, gmp-devel, libedit-devel +# libedit-devel > 2.11-2 correctly requires ncurses-devel +Requires: gcc, gmp-devel, libedit-devel > 2.11-2 Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 # introduced for f11 and to be removed for f13: Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed -BuildRequires: gmp-devel, libedit-devel +BuildRequires: gmp-devel, libedit-devel > 2.11-2 %if %{build_doc} BuildRequires: libxslt, docbook-style-xsl %endif @@ -192,6 +193,17 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf +%dir %{_docdir}/%{name} +%{_docdir}/%{name}/LICENSE +%dir %{_docdir}/%{name}/libraries +%{_docdir}/%{name}/libraries/gen_contents_index +%ghost %{_docdir}/%{name}/libraries/doc-index.html +%ghost %{_docdir}/%{name}/libraries/haddock.css +%ghost %{_docdir}/%{name}/libraries/haddock-util.js +%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif +%ghost %{_docdir}/%{name}/libraries/index.html +%ghost %{_docdir}/%{name}/libraries/minus.gif +%ghost %{_docdir}/%{name}/libraries/plus.gif %if %{build_prof} %files prof -f rpm-prof-filelist @@ -201,22 +213,17 @@ fi %if %{build_doc} %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) -%dir %{_docdir}/%{name} -%{_docdir}/%{name}/LICENSE %{_docdir}/%{name}/index.html -%{_docdir}/%{name}/libraries/gen_contents_index %{_docdir}/%{name}/libraries/prologue.txt -%dir %{_docdir}/%{name}/libraries -%ghost %{_docdir}/%{name}/libraries/doc-index.html -%ghost %{_docdir}/%{name}/libraries/haddock.css -%ghost %{_docdir}/%{name}/libraries/haddock-util.js -%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/libraries/index.html -%ghost %{_docdir}/%{name}/libraries/minus.gif -%ghost %{_docdir}/%{name}/libraries/plus.gif %endif %changelog +* Tue Feb 10 2009 Jens Petersen - 6.10.1-9 +- require and buildrequire libedit-devel > 2.11-2 +- move top doc dirs to main package for better sharing +- move gen_contents_index and ghost index files to main package +- protect ghc_register_pkg and ghc_unregister_pkg + * Fri Jan 23 2009 Jens Petersen - 6.10.1-8 - fix to libedit means can drop ncurses-devel BR workaround (#481252) From 574cea7124a890532737ca80574e6e1e6bc65682 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 13 Feb 2009 01:18:06 +0000 Subject: [PATCH 081/530] revert the last -doc files move changes for now --- ghc.spec | 28 +++++++++++++--------------- 1 file changed, 13 insertions(+), 15 deletions(-) diff --git a/ghc.spec b/ghc.spec index bedc328..d381032 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,8 +18,8 @@ Name: ghc Version: 6.10.1 Release: 9%{?dist} Summary: Glasgow Haskell Compilation system -# See https://bugzilla.redhat.com/bugzilla/show_bug.cgi?id=239713 -ExcludeArch: alpha ppc64 +# ghc has only been bootstrapped on the following archs for fedora: +ExclusiveArch: i386 x86_64 ppc License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -193,17 +193,6 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%dir %{_docdir}/%{name} -%{_docdir}/%{name}/LICENSE -%dir %{_docdir}/%{name}/libraries -%{_docdir}/%{name}/libraries/gen_contents_index -%ghost %{_docdir}/%{name}/libraries/doc-index.html -%ghost %{_docdir}/%{name}/libraries/haddock.css -%ghost %{_docdir}/%{name}/libraries/haddock-util.js -%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/libraries/index.html -%ghost %{_docdir}/%{name}/libraries/minus.gif -%ghost %{_docdir}/%{name}/libraries/plus.gif %if %{build_prof} %files prof -f rpm-prof-filelist @@ -213,15 +202,24 @@ fi %if %{build_doc} %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) +%dir %{_docdir}/%{name} +%{_docdir}/%{name}/LICENSE %{_docdir}/%{name}/index.html +%{_docdir}/%{name}/libraries/gen_contents_index %{_docdir}/%{name}/libraries/prologue.txt +%dir %{_docdir}/%{name}/libraries +%ghost %{_docdir}/%{name}/libraries/doc-index.html +%ghost %{_docdir}/%{name}/libraries/haddock.css +%ghost %{_docdir}/%{name}/libraries/haddock-util.js +%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif +%ghost %{_docdir}/%{name}/libraries/index.html +%ghost %{_docdir}/%{name}/libraries/minus.gif +%ghost %{_docdir}/%{name}/libraries/plus.gif %endif %changelog * Tue Feb 10 2009 Jens Petersen - 6.10.1-9 - require and buildrequire libedit-devel > 2.11-2 -- move top doc dirs to main package for better sharing -- move gen_contents_index and ghost index files to main package - protect ghc_register_pkg and ghc_unregister_pkg * Fri Jan 23 2009 Jens Petersen - 6.10.1-8 From cc989bbc316bcf7dc844949d92433ed6c2b8edbe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 13 Feb 2009 01:51:10 +0000 Subject: [PATCH 082/530] comment whitespace tweak --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d381032..5b81660 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 Source2: ghc-rpm-macros.ghc URL: http://haskell.org/ghc/ -# libedit-devel > 2.11-2 correctly requires ncurses-devel +# libedit-devel > 2.11-2 correctly requires ncurses-devel Requires: gcc, gmp-devel, libedit-devel > 2.11-2 Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) From 6269f30f2f9f7ca5c2a8c37e6b5cad52e1f78299 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 13 Feb 2009 02:15:56 +0000 Subject: [PATCH 083/530] update changelog timestamp --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5b81660..c6b29a9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -218,7 +218,7 @@ fi %endif %changelog -* Tue Feb 10 2009 Jens Petersen - 6.10.1-9 +* Fri Feb 13 2009 Jens Petersen - 6.10.1-9 - require and buildrequire libedit-devel > 2.11-2 - protect ghc_register_pkg and ghc_unregister_pkg From a00f693e620b921191493bda15e8da32d958c253 Mon Sep 17 00:00:00 2001 From: Jesse Keating Date: Tue, 24 Feb 2009 21:14:13 +0000 Subject: [PATCH 084/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_11_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c6b29a9..7663a27 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.1 -Release: 9%{?dist} +Release: 10%{?dist} Summary: Glasgow Haskell Compilation system # ghc has only been bootstrapped on the following archs for fedora: ExclusiveArch: i386 x86_64 ppc @@ -218,6 +218,9 @@ fi %endif %changelog +* Tue Feb 24 2009 Fedora Release Engineering - 6.10.1-10 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_11_Mass_Rebuild + * Fri Feb 13 2009 Jens Petersen - 6.10.1-9 - require and buildrequire libedit-devel > 2.11-2 - protect ghc_register_pkg and ghc_unregister_pkg From 7debd90bb1f5e554c9426a4fb1de7f32d8346851 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 25 Feb 2009 06:51:56 +0000 Subject: [PATCH 085/530] - use %%ix86 for change from i386 to i586 in rawhide - add ghc_archs macro in macros.ghc for other packages - obsolete haddock09 - use %%global instead of %%define - use bcond for doc and prof - rename ghc_gen_filelists lib filelist to -devel.files -------------------------------------------------------------------- --- ghc-rpm-macros.ghc | 10 ++++++---- ghc.spec | 42 +++++++++++++++++++++++++----------------- 2 files changed, 31 insertions(+), 21 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index b38f658..beeba5b 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,3 +1,5 @@ +%ghc_archs %{ix86} x86_64 ppc + %cabal %{_bindir}/runghc Setup %cabal_configure \ @@ -11,10 +13,10 @@ make -f cabal-rpm.mk %{_smp_mflags} \ %cabal_install %cabal copy --destdir=${RPM_BUILD_ROOT} -v %ghc_gen_filelists() \ -rm -f %1.files %1-prof.files \ -echo '%defattr(-,root,root,-)' > %1.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1.files \ +rm -f %1-devel.files %1-prof.files \ +echo '%defattr(-,root,root,-)' > %1-devel.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1-devel.files \ +find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1-devel.files \ echo '%defattr(-,root,root,-)' > %1-prof.files \ find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1.files %1-prof.files \ diff --git a/ghc.spec b/ghc.spec index 7663a27..8c2a4fc 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,6 +1,6 @@ -# speed up test builds by not building profiled libraries -%define build_prof 1 -%define build_doc 1 +# test builds can made faster by disabling profiled libraries +%bcond_without prof +%bcond_without doc # Fixing packaging problems can be a tremendous pain because it # generally requires a complete rebuild, which takes hours. To offset @@ -12,14 +12,14 @@ # # Obviously, this can only work if you leave the build section # completely untouched between builds. -%define package_debugging 0 +%global package_debugging 0 Name: ghc Version: 6.10.1 -Release: 10%{?dist} +Release: 11%{?dist} Summary: Glasgow Haskell Compilation system # ghc has only been bootstrapped on the following archs for fedora: -ExclusiveArch: i386 x86_64 ppc +ExclusiveArch: %{ix86} x86_64 ppc License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -30,12 +30,12 @@ URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel, libedit-devel > 2.11-2 Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0 +Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 # introduced for f11 and to be removed for f13: Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel > 2.11-2 -%if %{build_doc} +%if %{with doc} BuildRequires: libxslt, docbook-style-xsl %endif Patch1: ghc-6.10.1-gen_contexts_index.patch @@ -50,7 +50,7 @@ collection of libraries, and support for various language extensions, including concurrency, exceptions, and a foreign language interface. -%if %{build_prof} +%if %{with prof} %package prof Summary: Profiling libraries for GHC Group: Development/Libraries @@ -76,7 +76,7 @@ Compilation System (GHC) and its libraries. It should be installed if you like to have local access to the documentation in HTML format. # the debuginfo subpackage is currently empty anyway, so don't generate it -%define debug_package %{nil} +%global debug_package %{nil} %prep %setup -q -n %{name}-%{version} -b1 @@ -92,12 +92,12 @@ popd exit 0 %endif -%if !%{build_prof} +%if !%{with prof} echo "GhcLibWays=" >> mk/build.mk echo "GhcRTSWays=thr debug" >> mk/build.mk %endif -%if %{build_doc} +%if %{with doc} echo "XMLDocWays = html" >> mk/build.mk echo "HADDOCK_DOCS = YES" >> mk/build.mk %endif @@ -111,7 +111,7 @@ echo "HADDOCK_DOCS = YES" >> mk/build.mk make %{_smp_mflags} make %{_smp_mflags} -C libraries -%if %{build_doc} +%if %{with doc} make %{_smp_mflags} html %endif @@ -120,7 +120,7 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -%if %{build_doc} +%if %{with doc} make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif @@ -139,7 +139,7 @@ rm -f rpm-*-filelist rpm-*.files sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files cat rpm-dir.files rpm-lib.files > rpm-base-filelist -%if %{build_prof} +%if %{with prof} cat rpm-prof.files > rpm-prof-filelist %endif @@ -194,12 +194,12 @@ fi %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%if %{build_prof} +%if %{with prof} %files prof -f rpm-prof-filelist %defattr(-,root,root,-) %endif -%if %{build_doc} +%if %{with doc} %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) %dir %{_docdir}/%{name} @@ -218,6 +218,14 @@ fi %endif %changelog +* Wed Feb 25 2009 Jens Petersen - 6.10.1-11 +- use %%ix86 for change from i386 to i586 in rawhide +- add ghc_archs macro in macros.ghc for other packages +- obsolete haddock09 +- use %%global instead of %%define +- use bcond for doc and prof +- rename ghc_gen_filelists lib filelist to -devel.files + * Tue Feb 24 2009 Fedora Release Engineering - 6.10.1-10 - Rebuilt for https://fedoraproject.org/wiki/Fedora_11_Mass_Rebuild From 64f30a94e86dfed2b31fdb8a805f1bc71543ec86 Mon Sep 17 00:00:00 2001 From: Oliver Falk Date: Thu, 26 Feb 2009 09:34:42 +0000 Subject: [PATCH 086/530] Reenable build on alpha, after we finally managed to build ghc --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8c2a4fc..01531d3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -19,7 +19,7 @@ Version: 6.10.1 Release: 11%{?dist} Summary: Glasgow Haskell Compilation system # ghc has only been bootstrapped on the following archs for fedora: -ExclusiveArch: %{ix86} x86_64 ppc +ExclusiveArch: %{ix86} x86_64 ppc alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 From a5fa326f81e1748c01ef0a4f025daa1abad39752 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Feb 2009 01:05:09 +0000 Subject: [PATCH 087/530] - drop ghc_archs since it breaks koji - fix missing -devel in ghc_gen_filelists - change from ExclusiveArch to ExcludeArch ppc64 since alpha was bootstrapped by oliver --- ghc-rpm-macros.ghc | 4 +--- ghc.spec | 14 ++++++++++---- 2 files changed, 11 insertions(+), 7 deletions(-) diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index beeba5b..28111ca 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,5 +1,3 @@ -%ghc_archs %{ix86} x86_64 ppc - %cabal %{_bindir}/runghc Setup %cabal_configure \ @@ -19,7 +17,7 @@ find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1-devel.files find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1-devel.files \ echo '%defattr(-,root,root,-)' > %1-prof.files \ find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ -sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1.files %1-prof.files \ +sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1-devel.files %1-prof.files \ %{nil} %ghc_gen_scripts %cabal register --gen-script ; %cabal unregister --gen-script diff --git a/ghc.spec b/ghc.spec index 01531d3..57173dc 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,10 +16,10 @@ Name: ghc Version: 6.10.1 -Release: 11%{?dist} +Release: 12%{?dist} Summary: Glasgow Haskell Compilation system -# ghc has only been bootstrapped on the following archs for fedora: -ExclusiveArch: %{ix86} x86_64 ppc alpha +# fedora ghc has only been bootstrapped on ix86, x86_64, ppc, alpha: +ExcludeArch: ppc64 License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -218,6 +218,12 @@ fi %endif %changelog +* Fri Feb 27 2009 Jens Petersen - 6.10.1-12 +- drop ghc_archs since it breaks koji +- fix missing -devel in ghc_gen_filelists +- change from ExclusiveArch to ExcludeArch ppc64 since alpha was bootstrapped + by oliver + * Wed Feb 25 2009 Jens Petersen - 6.10.1-11 - use %%ix86 for change from i386 to i586 in rawhide - add ghc_archs macro in macros.ghc for other packages @@ -239,7 +245,7 @@ fi * Mon Jan 19 2009 Jens Petersen - 6.10.1-7 - buildrequire ncurses-devel to fix build of missing editline package needed for ghci line-editing (#478466) -- move spec templates to a haskell-packaging for easy updating +- move spec templates to cabal2spec package for easy updating - provide correct haddock version * Mon Dec 1 2008 Jens Petersen - 6.10.1-6 From 34b48fdbc805be013959a4d570e19672b65720a1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Feb 2009 03:44:31 +0000 Subject: [PATCH 088/530] - clean away tabs and excess whitespace padding - ExclusiveArch: %{ix86} x86_64 ppc alpha --- ghc.spec | 55 +++++++++++++++++++++++++++++-------------------------- 1 file changed, 29 insertions(+), 26 deletions(-) diff --git a/ghc.spec b/ghc.spec index 57173dc..a8cf23b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,31 +14,31 @@ # completely untouched between builds. %global package_debugging 0 -Name: ghc -Version: 6.10.1 -Release: 12%{?dist} -Summary: Glasgow Haskell Compilation system -# fedora ghc has only been bootstrapped on ix86, x86_64, ppc, alpha: -ExcludeArch: ppc64 -License: BSD -Group: Development/Languages -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 -Source2: ghc-rpm-macros.ghc -URL: http://haskell.org/ghc/ +Name: ghc +Version: 6.10.1 +Release: 13%{?dist} +Summary: Glasgow Haskell Compilation system +# fedora ghc has only been bootstrapped on the following archs: +ExclusiveArch: %{ix86} x86_64 ppc alpha +License: BSD +Group: Development/Languages +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 +Source2: ghc-rpm-macros.ghc +URL: http://haskell.org/ghc/ # libedit-devel > 2.11-2 correctly requires ncurses-devel -Requires: gcc, gmp-devel, libedit-devel > 2.11-2 +Requires: gcc, gmp-devel, libedit-devel > 2.11-2 Requires(post): policycoreutils -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 +BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 # introduced for f11 and to be removed for f13: -Provides: haddock = 2.3.0 -BuildRequires: ghc, happy, sed -BuildRequires: gmp-devel, libedit-devel > 2.11-2 +Provides: haddock = 2.3.0 +BuildRequires: ghc, happy, sed +BuildRequires: gmp-devel, libedit-devel > 2.11-2 %if %{with doc} BuildRequires: libxslt, docbook-style-xsl %endif -Patch1: ghc-6.10.1-gen_contexts_index.patch +Patch1: ghc-6.10.1-gen_contexts_index.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -52,10 +52,10 @@ interface. %if %{with prof} %package prof -Summary: Profiling libraries for GHC -Group: Development/Libraries -Requires: %{name} = %{version}-%{release} -Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof +Summary: Profiling libraries for GHC +Group: Development/Libraries +Requires: %{name} = %{version}-%{release} +Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System @@ -64,9 +64,9 @@ needed. %endif %package doc -Summary: Documentation for GHC -Group: Development/Languages -Requires: %{name} = %{version}-%{release} +Summary: Documentation for GHC +Group: Development/Languages +Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} @@ -218,6 +218,9 @@ fi %endif %changelog +* Fri Feb 27 2009 Jens Petersen - 6.10.1-13 +- ok let's stick with ExclusiveArch for brevity + * Fri Feb 27 2009 Jens Petersen - 6.10.1-12 - drop ghc_archs since it breaks koji - fix missing -devel in ghc_gen_filelists From c4a311b18060eecbd6c1eeb7c9fd2115e6bf6b08 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 5 Mar 2009 06:55:15 +0000 Subject: [PATCH 089/530] cabal2spec and templates now live in cabal2spec package --- cabal-bin-template.spec.in | 48 ------------ cabal-binlib-template.spec.in | 142 ---------------------------------- cabal-lib-template.spec.in | 131 ------------------------------- cabal2spec | 78 ------------------- 4 files changed, 399 deletions(-) delete mode 100644 cabal-bin-template.spec.in delete mode 100644 cabal-binlib-template.spec.in delete mode 100644 cabal-lib-template.spec.in delete mode 100755 cabal2spec diff --git a/cabal-bin-template.spec.in b/cabal-bin-template.spec.in deleted file mode 100644 index a69f081..0000000 --- a/cabal-bin-template.spec.in +++ /dev/null @@ -1,48 +0,0 @@ -# ghc does not emit debug information -%define debug_package %{nil} - -Name: @PACKAGE@ -Version: @VERSION@ -Release: 1%{?dist} -Summary: *FIXME* - -Group: *FIXME* -License: BSD? -URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} -Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -ExclusiveArch: i386 x86_64 ppc - -BuildRequires: ghc - -%description -*FIXME* - - -%prep -%setup -q - - -%build -%cabal_configure -%cabal build - - -%install -rm -rf $RPM_BUILD_ROOT -%cabal_install - - -%clean -rm -rf $RPM_BUILD_ROOT - - -%files -%defattr(-,root,root,-) -%doc LICENSE -%{_bindir}/%{name} - - -%changelog -* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 -- initial packaging for Fedora created by cabal2spec diff --git a/cabal-binlib-template.spec.in b/cabal-binlib-template.spec.in deleted file mode 100644 index 9fc7e2e..0000000 --- a/cabal-binlib-template.spec.in +++ /dev/null @@ -1,142 +0,0 @@ -%define ghc_version @GHC_VERSION@ - -%define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{name}-%{version} -%define pkg_docdir %{_docdir}/ghc/libraries/%{name}-%{version} - -%bcond_without prof -%bcond_without doc - -# ghc does not emit debug information -%define debug_package %{nil} - -Name: @PACKAGE@ -Version: @VERSION@ -Release: 1%{?dist} -Summary: *FIXME* - -Group: *FIXME* -License: BSD? *FIXME* -URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{name} -Source0: http://hackage.haskell.org/packages/archive/%{name}/%{version}/%{name}-%{version}.tar.gz -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -# ghc has only been bootstrapped on the following archs: -ExclusiveArch: i386 x86_64 ppc -BuildRequires: ghc = %{ghc_version} -%if %{with prof} -BuildRequires: ghc-prof = %{ghc_version} -%endif - -%description -*FIXME* - - -%package -n ghc-%{name} -Summary: Haskell %{name} library *FIXME* -Group: Development/Libraries -Provides: ghc-%{name}-devel = %{version}-%{release} -Requires: ghc = %{ghc_version} -Requires(post): ghc = %{ghc_version} -Requires(preun): ghc = %{ghc_version} - -%description -n ghc-%{name} -Haskell %{name} library. *FIXME* - - -%if %{with doc} -%package -n ghc-%{name}-doc -Summary: Documentation for %{name} -Group: Development/Libraries -Requires: ghc-doc = %{ghc_version} -Requires(postun): ghc-doc = %{ghc_version} - -%description -n ghc-%{name}-doc -This package contains development documentation files for the %{name} library. -%endif - - -%if %{with prof} -%package -n ghc-%{name}-prof -Summary: Profiling libraries for %{name} -Group: Development/Libraries -Requires: ghc-%{name} = %{version}-%{release} -Requires: ghc-prof = %{ghc_version} - -%description -n ghc-%{name}-prof -This package contains profiling libraries for %{name}. -%endif - - -%prep -%setup -q - - -%build -%cabal_configure --ghc %{!?without_prof:-p} -%cabal build -%if %{with doc} -%cabal haddock -%endif -%ghc_gen_scripts - - -%install -rm -rf $RPM_BUILD_ROOT -%cabal_install -%ghc_install_scripts -%ghc_gen_filelists ghc-%{name} - - -%clean -rm -rf $RPM_BUILD_ROOT - - -%post -n ghc-%{name} -%ghc_register_pkg - - -%if %{with doc} -%post -n ghc-%{name}-doc -%ghc_reindex_haddock -%endif - - -%preun -n ghc-%{name} -if [ "$1" -eq 0 ] ; then - %ghc_unregister_pkg -fi - - -%if %{with doc} -%postun -n ghc-%{name}-doc -if [ "$1" -eq 0 ] ; then - %ghc_reindex_haddock -fi -%endif - - -%files -%defattr(-,root,root,-) -%doc LICENSE -%{_bindir}/%{name} - - -%files -n ghc-%{name} -f ghc-%{name}.files -%defattr(-,root,root,-) - - -%if %{with doc} -%files -n ghc-%{name}-doc -%defattr(-,root,root,-) -%{pkg_docdir} -%endif - - -%if %{with prof} -%files -n ghc-%{name}-prof -f ghc-%{name}-prof.files -%defattr(-,root,root,-) -%endif - - -%changelog -* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 -- initial packaging for Fedora created by cabal2spec diff --git a/cabal-lib-template.spec.in b/cabal-lib-template.spec.in deleted file mode 100644 index c8d6440..0000000 --- a/cabal-lib-template.spec.in +++ /dev/null @@ -1,131 +0,0 @@ -%define pkg_name @PACKAGE@ -%define ghc_version @GHC_VERSION@ - -%define pkg_libdir %{_libdir}/ghc-%{ghc_version}/%{pkg_name}-%{version} -%define pkg_docdir %{_docdir}/ghc/libraries/%{pkg_name}-%{version} - -%bcond_without prof -%bcond_without doc - -# ghc does not emit debug information -%define debug_package %{nil} - -Name: ghc-%{pkg_name} -Version: @VERSION@ -Release: 1%{?dist} -Summary: Haskell %{pkg_name} library *FIXME* - -Group: Development/Libraries -License: BSD? *FIXME* -URL: http://hackage.haskell.org/cgi-bin/hackage-scripts/package/%{pkg_name} -Source0: http://hackage.haskell.org/packages/archive/%{pkg_name}/%{version}/%{pkg_name}-%{version}.tar.gz -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) - -Provides: %{name}-devel = %{version}-%{release} -# ghc has only been bootstrapped on the following archs: -ExclusiveArch: i386 x86_64 ppc -BuildRequires: ghc = %{ghc_version} -%if %{with prof} -BuildRequires: ghc-prof = %{ghc_version} -%endif -Requires: ghc = %{ghc_version} -Requires(post): ghc = %{ghc_version} -Requires(preun): ghc = %{ghc_version} - -%description -Haskell %{pkg_name} library for ghc-%{ghc_version}. *FIXME* - - -%if %{with doc} -%package doc -Summary: Documentation for %{name} -Group: Development/Libraries -Requires: ghc-doc = %{ghc_version} -Requires(postun): ghc-doc = %{ghc_version} - -%description doc -This package contains development documentation files for the %{name} library. -%endif - - -%if %{with prof} -%package prof -Summary: Profiling libraries for %{name} -Group: Development/Libraries -Requires: %{name} = %{version}-%{release} -Requires: ghc-prof = %{ghc_version} - -%description prof -This package contains profiling libraries for %{name}. -%endif - - -%prep -%setup -q -n %{pkg_name}-%{version} - - -%build -%cabal_configure --ghc %{!?without_prof:-p} -%cabal build -%if %{with doc} -%cabal haddock -%endif -%ghc_gen_scripts - - -%install -rm -rf $RPM_BUILD_ROOT -%cabal_install -%ghc_install_scripts -%ghc_gen_filelists %{name} - - -%clean -rm -rf $RPM_BUILD_ROOT - - -%post -%ghc_register_pkg - - -%if %{with doc} -%post doc -%ghc_reindex_haddock -%endif - - -%preun -if [ "$1" -eq 0 ] ; then - %ghc_unregister_pkg -fi - - -%if %{with doc} -%postun doc -if [ "$1" -eq 0 ] ; then - %ghc_reindex_haddock -fi -%endif - - -%files -f %{name}.files -%defattr(-,root,root,-) -%doc LICENSE - - -%if %{with doc} -%files doc -%defattr(-,root,root,-) -%{pkg_docdir} -%endif - - -%if %{with prof} -%files prof -f %{name}-prof.files -%defattr(-,root,root,-) -%endif - - -%changelog -* @DATE@ @PACKAGER@ <@EMAIL@> - @VERSION@-1 -- initial packaging for Fedora created by cabal2spec diff --git a/cabal2spec b/cabal2spec deleted file mode 100755 index f1b9df2..0000000 --- a/cabal2spec +++ /dev/null @@ -1,78 +0,0 @@ -#!/bin/sh - -# Copyright (C) 2008-2009 Red Hat, Inc -# Written by Jens Petersen , 2008. -# -# This program is free software; you can redistribute it and/or modify -# it under the terms of the GNU General Public License as published by -# the Free Software Foundation; either version 2, or (at your option) -# any later version. -# -# This program is distributed in the hope that it will be useful, -# but WITHOUT ANY WARRANTY; without even the implied warranty of -# MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -# GNU General Public License for more details. -# -# You should have received a copy of the GNU General Public License -# along with this program; if not, write to the Free Software Foundation, -# Inc., 51 Franklin Street, Fifth Floor, Boston, MA 02110-1301, USA. - -set -e - -[ $# -ne 1 -o ! -r "$1" ] && echo "Usage: $(basename $0) [hackage.tar.gz|hackage.cabal]" && exit 1 - -FILE=$1 - -case $FILE in - *.tar.gz) - TARNAME_VER=$(basename $FILE .tar.gz) - TARVERSION=$(echo $TARNAME_VER | sed -e "s/.*-//") - TARNAME=$(echo $TARNAME_VER | sed -e "s/-$TARVERSION//") - WORKDIR=$(mktemp -d) - tar zxf $FILE -C $WORKDIR "*.cabal" - CABAL="$WORKDIR/*/*.cabal" ;; - *.cabal) - CABAL=$FILE ;; -esac - -NAME=$(grep -i ^name: $CABAL | sed -e "s/[Nn]ame:[ \t]*//") -if [ -n "$TARNAME" -a "$TARNAME" != "$NAME" ]; then - echo "Warning: tarball name ($TARNAME) and cabal name ($NAME) differ!" -fi - -VERSION=$(grep -i ^version: $CABAL | sed -e "s/[Vv]ersion:[ \t]*//") -if [ -n "$TARVERSION" -a "$TARVERSION" != "$VERSION" ]; then - echo "Warning: tarball version ($TARVERSION) and cabal version ($VERSION) differ!" -fi - -CABALFILENAME=$(basename $CABAL .cabal) -if [ "$CABALFILENAME" != "$NAME" ]; then - echo "Warning: .cabal filename ($CABALFILENAME) and cabal Name field ($NAME) differ!" -fi - - -if grep -qi exposed-modules: $CABAL; then - HAS_LIB=yes -fi - -if grep -qi executable $CABAL; then - HAS_BIN=yes -fi - -[ -d "$WORKDIR" ] && rm -r $WORKDIR - -if [ "$HAS_LIB" -a ! "$HAS_BIN" ]; then - PREFIX=ghc- -fi - -SPECFILE=$PREFIX$NAME.spec - -[ -r "$SPECFILE" ] && echo "$SPECFILE already exists!" && exit 1 - -cp /usr/share/ghc/cabal-${HAS_BIN:+bin}${HAS_LIB:+lib}-template.spec.in $SPECFILE - -echo "created $SPECFILE (${HAS_BIN:+bin}${HAS_LIB:+lib}) for $NAME-$VERSION" - -DATE=$(env LANG=C date +"%a %b %e %Y") - -sed -i -e "s/@PACKAGE@/$NAME/" -e "s/@GHC_VERSION@/$(ghc --numeric-version)/" -e "s/@VERSION@/$VERSION/" -e "s/@DATE@/$DATE/" $SPECFILE From 3c08c5160e04efd9fd3ba0488263a83c6cbfc45b Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 8 Apr 2009 20:56:33 +0000 Subject: [PATCH 090/530] Sources for GHC 6.10.2 --- .cvsignore | 4 ++-- sources | 4 ++-- 2 files changed, 4 insertions(+), 4 deletions(-) diff --git a/.cvsignore b/.cvsignore index 57d613f..757f0ae 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.10.1-src.tar.bz2 -ghc-6.10.1-src-extralibs.tar.bz2 +ghc-6.10.2-src.tar.bz2 +ghc-6.10.2-src-extralibs.tar.bz2 diff --git a/sources b/sources index 9a920d0..fba01d3 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -54c676a632b3d73cf526b06347522c32 ghc-6.10.1-src.tar.bz2 -4ff4590f1002ae1ff608874da8643c67 ghc-6.10.1-src-extralibs.tar.bz2 +243d5857e5aa5f2f86e5e4c4437973fb ghc-6.10.2-src.tar.bz2 +9415604386ca69ebe15f1054653aefaf ghc-6.10.2-src-extralibs.tar.bz2 From 1b7e30e4b7591c17dbfad57eb5e5f2f972cd12bb Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 8 Apr 2009 21:39:16 +0000 Subject: [PATCH 091/530] Update to GHC 6.10.2 --- ghc-6.10.1-gen_contexts_index.patch | 12 ------------ ghc.spec | 9 +++++---- 2 files changed, 5 insertions(+), 16 deletions(-) delete mode 100644 ghc-6.10.1-gen_contexts_index.patch diff --git a/ghc-6.10.1-gen_contexts_index.patch b/ghc-6.10.1-gen_contexts_index.patch deleted file mode 100644 index aff35a3..0000000 --- a/ghc-6.10.1-gen_contexts_index.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc/libraries/gen_contents_index~ ghc/libraries/gen_contents_index ---- ghc-6.10.1/libraries/gen_contents_index~ 2008-11-06 11:18:45.000000000 +1000 -+++ ghc-6.10.1/libraries/gen_contents_index 2008-11-10 17:53:12.000000000 +1000 -@@ -23,7 +23,7 @@ - - for HADDOCK_FILE in $HADDOCK_FILES - do -- NAME=` echo "$HADDOCK_FILE" | sed 's#/dist/.*##' | sed 's#.*/##' ` -+ NAME=` echo "$HADDOCK_FILE" | sed 's#/dist/.*##' | sed 's#.*/##' | sed 's#\.haddock##' ` - HADDOCK_ARGS="$HADDOCK_ARGS --read-interface=$NAME,$HADDOCK_FILE" - NAMES="$NAMES $NAME" - done diff --git a/ghc.spec b/ghc.spec index a8cf23b..72010ee 100644 --- a/ghc.spec +++ b/ghc.spec @@ -15,8 +15,8 @@ %global package_debugging 0 Name: ghc -Version: 6.10.1 -Release: 13%{?dist} +Version: 6.10.2 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -38,7 +38,6 @@ BuildRequires: gmp-devel, libedit-devel > 2.11-2 %if %{with doc} BuildRequires: libxslt, docbook-style-xsl %endif -Patch1: ghc-6.10.1-gen_contexts_index.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -80,7 +79,6 @@ you like to have local access to the documentation in HTML format. %prep %setup -q -n %{name}-%{version} -b1 -%patch1 -p1 -b .orig %build # hack for building a local test package quickly from a prebuilt tree @@ -218,6 +216,9 @@ fi %endif %changelog +* Wed Apr 08 2009 Bryan O'Sullivan - 6.10.2-1 +- Update to 6.10.2 + * Fri Feb 27 2009 Jens Petersen - 6.10.1-13 - ok let's stick with ExclusiveArch for brevity From 7b1f4da984b5b0741ea20543593dff08dd6540ef Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 19 Apr 2009 04:28:22 +0000 Subject: [PATCH 092/530] - add ghc-requires rpm script to generate ghc version dependencies (thanks to Till Maas) - update macros.ghc: - add %%ghcrequires to call above script - pkg_libdir and pkg_docdir no longer to appear in packages and replaced by ghcpkgdir and ghcdocdir inside macros.ghc - make filelist also for docs --- ghc-rpm-macros.ghc | 23 +++++++++++++++-------- ghc-rpm-requires | 21 +++++++++++++++++++++ ghc.spec | 18 +++++++++++++++++- 3 files changed, 53 insertions(+), 9 deletions(-) create mode 100644 ghc-rpm-requires diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 28111ca..15edcf1 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -1,7 +1,7 @@ %cabal %{_bindir}/runghc Setup %cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{pkg_docdir} --libsubdir='$compiler/$pkgid' +%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{ghcdocdir} --libsubdir='$compiler/$pkgid' %cabal_makefile \ %cabal makefile -f cabal-rpm.mk \ @@ -10,22 +10,29 @@ make -f cabal-rpm.mk %{_smp_mflags} \ %cabal_install %cabal copy --destdir=${RPM_BUILD_ROOT} -v +%ghcdocdir %{_docdir}/ghc/libraries/%{?pkg_name}%{!?pkg_name:%{name}}-%{version} +%ghcpkgdir %{_libdir}/ghc-%(ghc --numeric-version)/%{?pkg_name}%{!?pkg_name:%name}-%{version} + %ghc_gen_filelists() \ -rm -f %1-devel.files %1-prof.files \ +rm -f %1-devel.files %1-prof.files %1-doc.files \ echo '%defattr(-,root,root,-)' > %1-devel.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} -type d | sed 's/^/%dir /' >> %1-devel.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1-devel.files \ +find ${RPM_BUILD_ROOT}%{ghcpkgdir} -type d | sed 's/^/%dir /' >> %1-devel.files \ +find ${RPM_BUILD_ROOT}%{ghcpkgdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1-devel.files \ echo '%defattr(-,root,root,-)' > %1-prof.files \ -find ${RPM_BUILD_ROOT}%{pkg_libdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ +find ${RPM_BUILD_ROOT}%{ghcpkgdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1-devel.files %1-prof.files \ +echo '%defattr(-,root,root,-)' > %1-doc.files \ +echo '%{ghcdocdir}' >> %1-doc.files \ %{nil} %ghc_gen_scripts %cabal register --gen-script ; %cabal unregister --gen-script -%ghc_install_scripts install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{pkg_libdir} +%ghc_install_scripts install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{ghcpkgdir} -%ghc_register_pkg %{pkg_libdir}/register.sh >/dev/null || : +%ghc_register_pkg %{ghcpkgdir}/register.sh >/dev/null || : -%ghc_unregister_pkg %{pkg_libdir}/unregister.sh >/dev/null || : +%ghc_unregister_pkg %{ghcpkgdir}/unregister.sh >/dev/null || : %ghc_reindex_haddock ( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : + +%ghcrequires() %{expand:%(/usr/lib/rpm/ghc-requires %*)} diff --git a/ghc-rpm-requires b/ghc-rpm-requires new file mode 100644 index 0000000..1a01f65 --- /dev/null +++ b/ghc-rpm-requires @@ -0,0 +1,21 @@ +#! /bin/bash +# Author: Till Maas +# +# Use this script as follows in your spec to get versioned +# ghc requires for post and preun: +# +# %{expand:%(/usr/lib/ghc-script-requires.sh ghc post preun)} + +ghc_num_ver=$(ghc --numeric-version) + +PKG=$1 ; shift + +# rpm will run this script once before the BuildRequires are installed +# then it has to report nothing to avoid rpm complainng about the empty version +# after the "ghc =" +if [ -n "${ghc_num_ver}" ]; then + echo "Requires: $PKG = ${ghc_num_ver}" + for script in "$@"; do + echo "Requires(${script}): $PKG = ${ghc_num_ver}" + done +fi diff --git a/ghc.spec b/ghc.spec index 72010ee..692ad8e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.2 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -24,7 +24,10 @@ License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 +# /etc/rpm/macros.ghc Source2: ghc-rpm-macros.ghc +# /usr/lib/rpm/ghc-requires +Source3: ghc-rpm-requires URL: http://haskell.org/ghc/ # libedit-devel > 2.11-2 correctly requires ncurses-devel Requires: gcc, gmp-devel, libedit-devel > 2.11-2 @@ -125,6 +128,9 @@ make DESTDIR=${RPM_BUILD_ROOT} install-docs # install rpm macros mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc +# rpm script for ghc version deps +mkdir -p ${RPM_BUILD_ROOT}/%{_prefix}/lib/rpm +cp -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_prefix}/lib/rpm/ghc-requires SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files @@ -191,6 +197,7 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf +%attr(755,root,root) %{_prefix}/lib/rpm/ghc-requires %if %{with prof} %files prof -f rpm-prof-filelist @@ -216,6 +223,15 @@ fi %endif %changelog +* Sun Apr 19 2009 Jens Petersen - 6.10.2-2 +- add ghc-requires rpm script to generate ghc version dependencies + (thanks to Till Maas) +- update macros.ghc: + - add %%ghcrequires to call above script + - pkg_libdir and pkg_docdir obsoleted in packages and replaced + by ghcpkgdir and ghcdocdir inside macros.ghc + - make filelist also for docs + * Wed Apr 08 2009 Bryan O'Sullivan - 6.10.2-1 - Update to 6.10.2 From 43b24a206db5c661cf6447a1f77d9d9b718eded1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Apr 2009 07:28:14 +0000 Subject: [PATCH 093/530] - define ghc_version in macros.ghc in place of ghcrequires - drop ghc-requires script for now --- ghc-rpm-macros.ghc | 2 +- ghc-rpm-requires | 21 --------------------- ghc.spec | 8 +++++--- 3 files changed, 6 insertions(+), 25 deletions(-) delete mode 100644 ghc-rpm-requires diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc index 15edcf1..6103094 100644 --- a/ghc-rpm-macros.ghc +++ b/ghc-rpm-macros.ghc @@ -35,4 +35,4 @@ echo '%{ghcdocdir}' >> %1-doc.files \ %ghc_reindex_haddock ( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : -%ghcrequires() %{expand:%(/usr/lib/rpm/ghc-requires %*)} +%ghc_version %(ghc --numeric-version) diff --git a/ghc-rpm-requires b/ghc-rpm-requires deleted file mode 100644 index 1a01f65..0000000 --- a/ghc-rpm-requires +++ /dev/null @@ -1,21 +0,0 @@ -#! /bin/bash -# Author: Till Maas -# -# Use this script as follows in your spec to get versioned -# ghc requires for post and preun: -# -# %{expand:%(/usr/lib/ghc-script-requires.sh ghc post preun)} - -ghc_num_ver=$(ghc --numeric-version) - -PKG=$1 ; shift - -# rpm will run this script once before the BuildRequires are installed -# then it has to report nothing to avoid rpm complainng about the empty version -# after the "ghc =" -if [ -n "${ghc_num_ver}" ]; then - echo "Requires: $PKG = ${ghc_num_ver}" - for script in "$@"; do - echo "Requires(${script}): $PKG = ${ghc_num_ver}" - done -fi diff --git a/ghc.spec b/ghc.spec index 692ad8e..daf2e8d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,7 +16,7 @@ Name: ghc Version: 6.10.2 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -26,8 +26,6 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 # /etc/rpm/macros.ghc Source2: ghc-rpm-macros.ghc -# /usr/lib/rpm/ghc-requires -Source3: ghc-rpm-requires URL: http://haskell.org/ghc/ # libedit-devel > 2.11-2 correctly requires ncurses-devel Requires: gcc, gmp-devel, libedit-devel > 2.11-2 @@ -223,6 +221,10 @@ fi %endif %changelog +* Fri Apr 24 2009 Jens Petersen - 6.10.2-3 +- define ghc_version in macros.ghc in place of ghcrequires +- drop ghc-requires script for now + * Sun Apr 19 2009 Jens Petersen - 6.10.2-2 - add ghc-requires rpm script to generate ghc version dependencies (thanks to Till Maas) From a60b93f8dd1843dd4b288ab1b8a8548cd09dc496 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Apr 2009 07:59:57 +0000 Subject: [PATCH 094/530] remove ghc-requires from %install and %files --- ghc.spec | 4 ---- 1 file changed, 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index daf2e8d..eed1244 100644 --- a/ghc.spec +++ b/ghc.spec @@ -126,9 +126,6 @@ make DESTDIR=${RPM_BUILD_ROOT} install-docs # install rpm macros mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc -# rpm script for ghc version deps -mkdir -p ${RPM_BUILD_ROOT}/%{_prefix}/lib/rpm -cp -p %{SOURCE3} ${RPM_BUILD_ROOT}/%{_prefix}/lib/rpm/ghc-requires SRC_TOP=$PWD rm -f rpm-*-filelist rpm-*.files @@ -195,7 +192,6 @@ fi %{_bindir}/* %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%attr(755,root,root) %{_prefix}/lib/rpm/ghc-requires %if %{with prof} %files prof -f rpm-prof-filelist From e93fe4dedac654c53d0753c6e5d2c23ac6f17d74 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 28 Apr 2009 09:45:16 +0000 Subject: [PATCH 095/530] - add experimental bcond hscolour - BR libffi-devel - add experimental support for building shared libraries (for ghc-6.11) - add libs subpackage for shared libraries - create a ld.conf.d file for libghc*.so - drop redundant setting of GhcLibWays in build.mk for no prof - drop redundant setting of HADDOCK_DOCS - simplify filelist names - add a check section based on tests from debian package - be more careful about doc files in filelist --- ghc.spec | 121 +++++++++++++++++++++++++++++++++++++++++++------------ 1 file changed, 95 insertions(+), 26 deletions(-) diff --git a/ghc.spec b/ghc.spec index eed1244..e6a6968 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,7 +1,13 @@ -# test builds can made faster by disabling profiled libraries +# test builds can made faster and smaller by disabling profiled libraries %bcond_without prof +# build users_guide, etc %bcond_without doc +# experimental +## shared libraries support available in ghc >= 6.11 +%bcond_without shared +%bcond_with hscolour + # Fixing packaging problems can be a tremendous pain because it # generally requires a complete rebuild, which takes hours. To offset # the misery, do a complete build once using "rpmbuild -bc", then copy @@ -16,7 +22,7 @@ Name: ghc Version: 6.10.2 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -32,13 +38,18 @@ Requires: gcc, gmp-devel, libedit-devel > 2.11-2 Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 -# introduced for f11 and to be removed for f13: +# introduced for f11 and can be removed for f13: Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel > 2.11-2 +BuildRequires: libffi-devel %if %{with doc} BuildRequires: libxslt, docbook-style-xsl +%if %{with hscolour} +BuildRequires: hscolour +%endif %endif +Patch1: ghc-mk-pkg-install-inplace.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -75,11 +86,25 @@ Preformatted documentation for the Glorious Glasgow Haskell Compilation System (GHC) and its libraries. It should be installed if you like to have local access to the documentation in HTML format. +%if %{with shared} +%package libs +Summary: Shared libraries for GHC +Group: Development/Libraries +Requires: %{name} = %{version}-%{release} + +%description libs +Shared libraries for Glorious Glasgow Haskell Compilation System +(GHC). They should be installed to build standalone programs. +%endif + # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} %prep %setup -q -n %{name}-%{version} -b1 +%if %{with shared} +%patch1 -p1 -b .orig-dist-install +%endif %build # hack for building a local test package quickly from a prebuilt tree @@ -91,24 +116,23 @@ popd exit 0 %endif -%if !%{with prof} -echo "GhcLibWays=" >> mk/build.mk -echo "GhcRTSWays=thr debug" >> mk/build.mk +%if %{without prof} +echo "GhcLibWays=%{?with_shared:dyn}" >> mk/build.mk %endif %if %{with doc} echo "XMLDocWays = html" >> mk/build.mk -echo "HADDOCK_DOCS = YES" >> mk/build.mk %endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ + %{?with_shared:--enable-shared} make %{_smp_mflags} -make %{_smp_mflags} -C libraries +#make %{_smp_mflags} -C libraries %if %{with doc} make %{_smp_mflags} html @@ -123,24 +147,26 @@ make DESTDIR=${RPM_BUILD_ROOT} install make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif +%if %{with shared} +mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d +echo %{_libdir}/%{name}-%{version} > ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d/ghc-%{_arch}.conf +%endif + # install rpm macros mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc SRC_TOP=$PWD -rm -f rpm-*-filelist rpm-*.files +rm -f rpm-*.files ( cd $RPM_BUILD_ROOT find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf*' -fprint $SRC_TOP/rpm-lib.files \) - find .%{_docdir}/%{name}/* -type d ! -name libraries > $SRC_TOP/rpm-doc-dir.files + find .%{_docdir}/%{name}/* -type d ! -name libraries %{?with_hscolour:! -name src} > $SRC_TOP/rpm-doc-dir.files ) # make paths absolute (filter "./usr" to "/usr") sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files -cat rpm-dir.files rpm-lib.files > rpm-base-filelist -%if %{with prof} -cat rpm-prof.files > rpm-prof-filelist -%endif +cat rpm-dir.files rpm-lib.files > rpm-base.files # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -151,6 +177,20 @@ for i in hsc2hs runhaskell; do fi done +%check +# stolen from ghc6/debian/rules: +# Do some very simple tests that the compiler actually works +rm -rf testghc +mkdir testghc +echo 'main = putStrLn "Foo"' > testghc/foo.hs +ghc/stage2-inplace/ghc testghc/foo.hs -o testghc/foo +[ "$(testghc/foo)" = "Foo" ] +rm testghc/* +echo 'main = putStrLn "Foo"' > testghc/foo.hs +ghc/stage2-inplace/ghc testghc/foo.hs -o testghc/foo -O2 +[ "$(testghc/foo)" = "Foo" ] +rm testghc/* + %clean rm -rf $RPM_BUILD_ROOT @@ -175,9 +215,9 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 -# posttrans to make sure any old documentation has been removed first -%posttrans doc -( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : +%if %{with shared} +%post libs -p /sbin/ldconfig +%endif %preun if [ "$1" = 0 ]; then @@ -185,25 +225,31 @@ if [ "$1" = 0 ]; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi -%files -f rpm-base-filelist +%if %{with shared} +%postun libs -p /sbin/ldconfig +%endif + +%posttrans doc +# (posttrans to make sure any old documentation has been removed first) +( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : + +%files -f rpm-base.files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README -%doc %{_mandir}/man1/ghc.* %{_bindir}/* +%if %{with doc} +%{_mandir}/man1/ghc.* +%endif %{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf -%if %{with prof} -%files prof -f rpm-prof-filelist -%defattr(-,root,root,-) -%endif - -%if %{with doc} %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) %dir %{_docdir}/%{name} %{_docdir}/%{name}/LICENSE +%if %{with doc} %{_docdir}/%{name}/index.html +%endif %{_docdir}/%{name}/libraries/gen_contents_index %{_docdir}/%{name}/libraries/prologue.txt %dir %{_docdir}/%{name}/libraries @@ -214,9 +260,32 @@ fi %ghost %{_docdir}/%{name}/libraries/index.html %ghost %{_docdir}/%{name}/libraries/minus.gif %ghost %{_docdir}/%{name}/libraries/plus.gif + +%if %{with shared} +%files libs +%defattr(-,root,root,-) +%{_sysconfdir}/ld.so.conf.d/ghc-%{_arch}.conf +%{_libdir}/libHS*-ghc%{version}.so +%endif + +%if %{with prof} +%files prof -f rpm-prof.files +%defattr(-,root,root,-) %endif %changelog +* Tue Apr 28 2009 Jens Petersen - 6.10.2-4 +- add experimental bcond hscolour +- BR libffi-devel +- add experimental support for building shared libraries (for ghc-6.11) + - add libs subpackage for shared libraries + - create a ld.conf.d file for libghc*.so +- drop redundant setting of GhcLibWays in build.mk for no prof +- drop redundant setting of HADDOCK_DOCS +- simplify filelist names +- add a check section based on tests from debian's package +- be more careful about doc files in filelist + * Fri Apr 24 2009 Jens Petersen - 6.10.2-3 - define ghc_version in macros.ghc in place of ghcrequires - drop ghc-requires script for now From f654d302ae45369e7e9513e9e3f56f1c9b36c12e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 28 Apr 2009 09:59:05 +0000 Subject: [PATCH 096/530] add patch --- ghc-mk-pkg-install-inplace.patch | 24 ++++++++++++++++++++++++ 1 file changed, 24 insertions(+) create mode 100644 ghc-mk-pkg-install-inplace.patch diff --git a/ghc-mk-pkg-install-inplace.patch b/ghc-mk-pkg-install-inplace.patch new file mode 100644 index 0000000..f49bd30 --- /dev/null +++ b/ghc-mk-pkg-install-inplace.patch @@ -0,0 +1,24 @@ +diff -up ghc-6.11.20090421/mk/cabal-flags.mk~ ghc-6.11.20090421/mk/cabal-flags.mk +--- ghc-6.11.20090421/mk/cabal-flags.mk~ 2009-04-22 03:15:57.000000000 +1000 ++++ ghc-6.11.20090421/mk/cabal-flags.mk 2009-04-26 12:06:06.000000000 +1000 +@@ -3,7 +3,7 @@ nothing= + space=$(nothing) $(nothing) + comma=, + +-GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-install/build/ghc-pkg/ghc-pkg ++GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-inplace/build/ghc-pkg/ghc-pkg + + LIBRARIES_ABS = $(FPTOOLS_TOP_ABS)/libraries + UTILS_ABS = $(FPTOOLS_TOP_ABS)/utils +diff -up ghc-6.11.20090421/mk/package.mk~ ghc-6.11.20090421/mk/package.mk +--- ghc-6.11.20090421/mk/package.mk~ 2009-04-22 03:15:55.000000000 +1000 ++++ ghc-6.11.20090421/mk/package.mk 2009-04-26 10:52:55.000000000 +1000 +@@ -86,7 +86,7 @@ install:: + | sed -e 's/""//g' -e 's/:[ ]*,/: /g' \ + | $(GHC_PKG_INSTALL_PROG) --global-conf $(DESTDIR)$(datadir)/package.conf update - --force + +-GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-install/build/ghc-pkg/ghc-pkg ++GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-inplace/build/ghc-pkg/ghc-pkg + + # we could be more accurate here and add a dependency on + # driver/package.conf, but that doesn't work too well because of From fbbca4c56fcfc557b401948ee7f4afd800b30f87 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 28 Apr 2009 10:09:37 +0000 Subject: [PATCH 097/530] only BR libffi-devel for shared build --- ghc.spec | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index e6a6968..4bb604f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -42,7 +42,9 @@ Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel > 2.11-2 +%if %{with shared} BuildRequires: libffi-devel +%endif %if %{with doc} BuildRequires: libxslt, docbook-style-xsl %if %{with hscolour} @@ -276,10 +278,10 @@ fi %changelog * Tue Apr 28 2009 Jens Petersen - 6.10.2-4 - add experimental bcond hscolour -- BR libffi-devel - add experimental support for building shared libraries (for ghc-6.11) - add libs subpackage for shared libraries - create a ld.conf.d file for libghc*.so + - BR libffi-devel - drop redundant setting of GhcLibWays in build.mk for no prof - drop redundant setting of HADDOCK_DOCS - simplify filelist names From 12ad68912d7afa93017f5cd7f5e1ffcdb9423b9e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 29 Apr 2009 07:33:54 +0000 Subject: [PATCH 098/530] remember to actually turn off shared libs for now --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 4bb604f..98fa234 100644 --- a/ghc.spec +++ b/ghc.spec @@ -5,7 +5,7 @@ # experimental ## shared libraries support available in ghc >= 6.11 -%bcond_without shared +%bcond_with shared %bcond_with hscolour # Fixing packaging problems can be a tremendous pain because it @@ -43,6 +43,7 @@ Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel, libedit-devel > 2.11-2 %if %{with shared} +# not sure if this is actually needed BuildRequires: libffi-devel %endif %if %{with doc} From 773bb46c70bee9122457462b00353b823f6f3079 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 2 May 2009 06:57:24 +0000 Subject: [PATCH 099/530] try unregisterised ppc to see if that stops the segfaulting with runghc --- ghc.spec | 11 ++++++++++- 1 file changed, 10 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 98fa234..d0a7b2a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Name: ghc Version: 6.10.2 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -119,6 +119,12 @@ popd exit 0 %endif +%ifarch ppc +echo "GhcUnregisterised=YES" >> mk/build.mk +echo "GhcWithNativeCodeGen=NO" >> mk/build.mk +echo "SplitObjs=NO" >> mk/build.mk +%endif + %if %{without prof} echo "GhcLibWays=%{?with_shared:dyn}" >> mk/build.mk %endif @@ -277,6 +283,9 @@ fi %endif %changelog +* Sat May 2 2009 Jens Petersen - 6.10.2-5 +- try unregisterised ppc to see if that stops the segfaulting with runghc + * Tue Apr 28 2009 Jens Petersen - 6.10.2-4 - add experimental bcond hscolour - add experimental support for building shared libraries (for ghc-6.11) From 4d88e55f200776b06a8fd2a01fab567e23f749f5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 13 May 2009 07:17:04 +0000 Subject: [PATCH 100/530] - update to 6.10.3 - macros.ghc moved to ghc-rpm-macros package - fix handling of hscolor files in filelist generation - give up ppc unregisterized build since it failed --- .cvsignore | 4 ++-- ghc.spec | 25 +++++++------------------ sources | 4 ++-- 3 files changed, 11 insertions(+), 22 deletions(-) diff --git a/.cvsignore b/.cvsignore index 757f0ae..8b09f7c 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.10.2-src.tar.bz2 -ghc-6.10.2-src-extralibs.tar.bz2 +ghc-6.10.3-src.tar.bz2 +ghc-6.10.3-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index d0a7b2a..424c751 100644 --- a/ghc.spec +++ b/ghc.spec @@ -21,8 +21,8 @@ %global package_debugging 0 Name: ghc -Version: 6.10.2 -Release: 5%{?dist} +Version: 6.10.3 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -30,8 +30,6 @@ License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 -# /etc/rpm/macros.ghc -Source2: ghc-rpm-macros.ghc URL: http://haskell.org/ghc/ # libedit-devel > 2.11-2 correctly requires ncurses-devel Requires: gcc, gmp-devel, libedit-devel > 2.11-2 @@ -119,12 +117,6 @@ popd exit 0 %endif -%ifarch ppc -echo "GhcUnregisterised=YES" >> mk/build.mk -echo "GhcWithNativeCodeGen=NO" >> mk/build.mk -echo "SplitObjs=NO" >> mk/build.mk -%endif - %if %{without prof} echo "GhcLibWays=%{?with_shared:dyn}" >> mk/build.mk %endif @@ -161,15 +153,11 @@ mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d echo %{_libdir}/%{name}-%{version} > ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d/ghc-%{_arch}.conf %endif -# install rpm macros -mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm -cp -p %{SOURCE2} ${RPM_BUILD_ROOT}/%{_sysconfdir}/rpm/macros.ghc - SRC_TOP=$PWD rm -f rpm-*.files ( cd $RPM_BUILD_ROOT find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf*' -fprint $SRC_TOP/rpm-lib.files \) - find .%{_docdir}/%{name}/* -type d ! -name libraries %{?with_hscolour:! -name src} > $SRC_TOP/rpm-doc-dir.files + find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files ) # make paths absolute (filter "./usr" to "/usr") @@ -249,7 +237,6 @@ fi %if %{with doc} %{_mandir}/man1/ghc.* %endif -%{_sysconfdir}/rpm/macros.ghc %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %files doc -f rpm-doc-dir.files @@ -283,8 +270,10 @@ fi %endif %changelog -* Sat May 2 2009 Jens Petersen - 6.10.2-5 -- try unregisterised ppc to see if that stops the segfaulting with runghc +* Wed May 13 2009 Jens Petersen - 6.10.3-1 +- update to 6.10.3 +- macros.ghc moved to ghc-rpm-macros package +- fix handling of hscolor files in filelist generation * Tue Apr 28 2009 Jens Petersen - 6.10.2-4 - add experimental bcond hscolour diff --git a/sources b/sources index fba01d3..e41535f 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -243d5857e5aa5f2f86e5e4c4437973fb ghc-6.10.2-src.tar.bz2 -9415604386ca69ebe15f1054653aefaf ghc-6.10.2-src-extralibs.tar.bz2 +3de6a6d434c2b43def10c4cc613b265e ghc-6.10.3-src.tar.bz2 +d0fe09625556ea274df11d601c1b2a15 ghc-6.10.3-src-extralibs.tar.bz2 From e092da1081611b80fc893a1d084fb3f4186e3e71 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 13 May 2009 07:23:07 +0000 Subject: [PATCH 101/530] editline is no longer needed to build --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 424c751..2c640b0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,15 +31,14 @@ Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 URL: http://haskell.org/ghc/ -# libedit-devel > 2.11-2 correctly requires ncurses-devel -Requires: gcc, gmp-devel, libedit-devel > 2.11-2 +Requires: gcc, gmp-devel Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 # introduced for f11 and can be removed for f13: Provides: haddock = 2.3.0 BuildRequires: ghc, happy, sed -BuildRequires: gmp-devel, libedit-devel > 2.11-2 +BuildRequires: gmp-devel %if %{with shared} # not sure if this is actually needed BuildRequires: libffi-devel @@ -272,6 +271,7 @@ fi %changelog * Wed May 13 2009 Jens Petersen - 6.10.3-1 - update to 6.10.3 +- haskline replaces editline, so it is no longer needed to build - macros.ghc moved to ghc-rpm-macros package - fix handling of hscolor files in filelist generation From 2a45ca8be229b941f681466583951ce128b0cf96 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 21 May 2009 00:05:07 +0000 Subject: [PATCH 102/530] remove macros.ghc since they now live in ghc-rpm-macros --- ghc-rpm-macros.ghc | 38 -------------------------------------- 1 file changed, 38 deletions(-) delete mode 100644 ghc-rpm-macros.ghc diff --git a/ghc-rpm-macros.ghc b/ghc-rpm-macros.ghc deleted file mode 100644 index 6103094..0000000 --- a/ghc-rpm-macros.ghc +++ /dev/null @@ -1,38 +0,0 @@ -%cabal %{_bindir}/runghc Setup - -%cabal_configure \ -%cabal configure --prefix=%{_prefix} --libdir=%{_libdir} --docdir=%{_docdir}/%{name}-%{version} --htmldir=%{ghcdocdir} --libsubdir='$compiler/$pkgid' - -%cabal_makefile \ -%cabal makefile -f cabal-rpm.mk \ -make -f cabal-rpm.mk %{_smp_mflags} \ -%{nil} - -%cabal_install %cabal copy --destdir=${RPM_BUILD_ROOT} -v - -%ghcdocdir %{_docdir}/ghc/libraries/%{?pkg_name}%{!?pkg_name:%{name}}-%{version} -%ghcpkgdir %{_libdir}/ghc-%(ghc --numeric-version)/%{?pkg_name}%{!?pkg_name:%name}-%{version} - -%ghc_gen_filelists() \ -rm -f %1-devel.files %1-prof.files %1-doc.files \ -echo '%defattr(-,root,root,-)' > %1-devel.files \ -find ${RPM_BUILD_ROOT}%{ghcpkgdir} -type d | sed 's/^/%dir /' >> %1-devel.files \ -find ${RPM_BUILD_ROOT}%{ghcpkgdir} ! \\( -type d -o -name '*_p.a' -o -name '*.p_hi' \\) >> %1-devel.files \ -echo '%defattr(-,root,root,-)' > %1-prof.files \ -find ${RPM_BUILD_ROOT}%{ghcpkgdir} \\( -name '*_p.a' -o -name '*.p_hi' \\) >> %1-prof.files \ -sed -i -e "s!${RPM_BUILD_ROOT}!!g" %1-devel.files %1-prof.files \ -echo '%defattr(-,root,root,-)' > %1-doc.files \ -echo '%{ghcdocdir}' >> %1-doc.files \ -%{nil} - -%ghc_gen_scripts %cabal register --gen-script ; %cabal unregister --gen-script - -%ghc_install_scripts install -m 755 register.sh unregister.sh ${RPM_BUILD_ROOT}%{ghcpkgdir} - -%ghc_register_pkg %{ghcpkgdir}/register.sh >/dev/null || : - -%ghc_unregister_pkg %{ghcpkgdir}/unregister.sh >/dev/null || : - -%ghc_reindex_haddock ( cd %{_docdir}/ghc/libraries && [ -x "./gen_contents_index" ] && ./gen_contents_index ) || : - -%ghc_version %(ghc --numeric-version) From f7351e60859040d59e337e64f1e1159b5c551da1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 22 May 2009 03:17:29 +0000 Subject: [PATCH 103/530] update haddock provides --- ghc.spec | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2c640b0..4f31301 100644 --- a/ghc.spec +++ b/ghc.spec @@ -21,8 +21,9 @@ %global package_debugging 0 Name: ghc +# part of haskell-platform Version: 6.10.3 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -34,9 +35,10 @@ URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock <= 2.0.0.0, haddock09 +Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 # introduced for f11 and can be removed for f13: -Provides: haddock = 2.3.0 +Obsoletes: haddock < 2.4.2 +Provides: haddock = 2.4.2 BuildRequires: ghc, happy, sed BuildRequires: gmp-devel %if %{with shared} @@ -269,6 +271,9 @@ fi %endif %changelog +* Fri May 22 2009 Jens Petersen - 6.10.3-2 +- update haddock provides + * Wed May 13 2009 Jens Petersen - 6.10.3-1 - update to 6.10.3 - haskline replaces editline, so it is no longer needed to build From 5c4b5faefff70a18e7837ff98a0d6a6e644048bb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 22 May 2009 04:29:13 +0000 Subject: [PATCH 104/530] - drop ghc-mk-pkg-install-inplace.patch: no longer needed with new 6.11 buildsys - add bcond for extralibs - rename doc bcond to manual --- ghc-mk-pkg-install-inplace.patch | 24 ------------------------ ghc.spec | 32 ++++++++++++++++++-------------- 2 files changed, 18 insertions(+), 38 deletions(-) delete mode 100644 ghc-mk-pkg-install-inplace.patch diff --git a/ghc-mk-pkg-install-inplace.patch b/ghc-mk-pkg-install-inplace.patch deleted file mode 100644 index f49bd30..0000000 --- a/ghc-mk-pkg-install-inplace.patch +++ /dev/null @@ -1,24 +0,0 @@ -diff -up ghc-6.11.20090421/mk/cabal-flags.mk~ ghc-6.11.20090421/mk/cabal-flags.mk ---- ghc-6.11.20090421/mk/cabal-flags.mk~ 2009-04-22 03:15:57.000000000 +1000 -+++ ghc-6.11.20090421/mk/cabal-flags.mk 2009-04-26 12:06:06.000000000 +1000 -@@ -3,7 +3,7 @@ nothing= - space=$(nothing) $(nothing) - comma=, - --GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-install/build/ghc-pkg/ghc-pkg -+GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-inplace/build/ghc-pkg/ghc-pkg - - LIBRARIES_ABS = $(FPTOOLS_TOP_ABS)/libraries - UTILS_ABS = $(FPTOOLS_TOP_ABS)/utils -diff -up ghc-6.11.20090421/mk/package.mk~ ghc-6.11.20090421/mk/package.mk ---- ghc-6.11.20090421/mk/package.mk~ 2009-04-22 03:15:55.000000000 +1000 -+++ ghc-6.11.20090421/mk/package.mk 2009-04-26 10:52:55.000000000 +1000 -@@ -86,7 +86,7 @@ install:: - | sed -e 's/""//g' -e 's/:[ ]*,/: /g' \ - | $(GHC_PKG_INSTALL_PROG) --global-conf $(DESTDIR)$(datadir)/package.conf update - --force - --GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-install/build/ghc-pkg/ghc-pkg -+GHC_PKG_INSTALL_PROG = $(FPTOOLS_TOP_ABS)/utils/ghc-pkg/dist-inplace/build/ghc-pkg/ghc-pkg - - # we could be more accurate here and add a dependency on - # driver/package.conf, but that doesn't work too well because of diff --git a/ghc.spec b/ghc.spec index 4f31301..570940f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,11 +1,15 @@ # test builds can made faster and smaller by disabling profiled libraries +# (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof # build users_guide, etc -%bcond_without doc +%bcond_without manual +# include extralibs +%bcond_without extralibs # experimental ## shared libraries support available in ghc >= 6.11 %bcond_with shared +## include colored html src %bcond_with hscolour # Fixing packaging problems can be a tremendous pain because it @@ -30,7 +34,9 @@ ExclusiveArch: %{ix86} x86_64 ppc alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +%if %{with extralibs} Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 +%endif URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel Requires(post): policycoreutils @@ -45,13 +51,12 @@ BuildRequires: gmp-devel # not sure if this is actually needed BuildRequires: libffi-devel %endif -%if %{with doc} +%if %{with manual} BuildRequires: libxslt, docbook-style-xsl +%endif %if %{with hscolour} BuildRequires: hscolour %endif -%endif -Patch1: ghc-mk-pkg-install-inplace.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -103,10 +108,7 @@ Shared libraries for Glorious Glasgow Haskell Compilation System %global debug_package %{nil} %prep -%setup -q -n %{name}-%{version} -b1 -%if %{with shared} -%patch1 -p1 -b .orig-dist-install -%endif +%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %build # hack for building a local test package quickly from a prebuilt tree @@ -122,7 +124,7 @@ exit 0 echo "GhcLibWays=%{?with_shared:dyn}" >> mk/build.mk %endif -%if %{with doc} +%if %{with manual} echo "XMLDocWays = html" >> mk/build.mk %endif @@ -134,9 +136,8 @@ echo "XMLDocWays = html" >> mk/build.mk %{?with_shared:--enable-shared} make %{_smp_mflags} -#make %{_smp_mflags} -C libraries -%if %{with doc} +%if %{with manual} make %{_smp_mflags} html %endif @@ -145,7 +146,7 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -%if %{with doc} +%if %{with manual} make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif @@ -235,7 +236,7 @@ fi %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* -%if %{with doc} +%if %{with manual} %{_mandir}/man1/ghc.* %endif %config(noreplace) %{_libdir}/ghc-%{version}/package.conf @@ -244,7 +245,7 @@ fi %defattr(-,root,root,-) %dir %{_docdir}/%{name} %{_docdir}/%{name}/LICENSE -%if %{with doc} +%if %{with manual} %{_docdir}/%{name}/index.html %endif %{_docdir}/%{name}/libraries/gen_contents_index @@ -273,6 +274,9 @@ fi %changelog * Fri May 22 2009 Jens Petersen - 6.10.3-2 - update haddock provides +- drop ghc-mk-pkg-install-inplace.patch: no longer needed with new 6.11 buildsys +- add bcond for extralibs +- rename doc bcond to manual * Wed May 13 2009 Jens Petersen - 6.10.3-1 - update to 6.10.3 From 16c9fecedf2a367b6f1dfe2950163e6b3c848328 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 28 May 2009 00:11:55 +0000 Subject: [PATCH 105/530] tweak haddock changelog comment --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 570940f..8e55e7f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -273,7 +273,7 @@ fi %changelog * Fri May 22 2009 Jens Petersen - 6.10.3-2 -- update haddock provides +- update haddock provides and obsoletes - drop ghc-mk-pkg-install-inplace.patch: no longer needed with new 6.11 buildsys - add bcond for extralibs - rename doc bcond to manual From 95a0f6c3c6d8b893fe17da26bd95b10272c4b74c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 30 May 2009 06:16:53 +0000 Subject: [PATCH 106/530] - add haddock_version and use it to obsolete haddock and ghc-haddock-* --- ghc.spec | 41 +++++++++++++++++++++++++---------------- 1 file changed, 25 insertions(+), 16 deletions(-) diff --git a/ghc.spec b/ghc.spec index 8e55e7f..1a8af4a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -12,6 +12,8 @@ ## include colored html src %bcond_with hscolour +%global haddock_version 2.4.2 + # Fixing packaging problems can be a tremendous pain because it # generally requires a complete rebuild, which takes hours. To offset # the misery, do a complete build once using "rpmbuild -bc", then copy @@ -27,7 +29,7 @@ Name: ghc # part of haskell-platform Version: 6.10.3 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -43,8 +45,8 @@ Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 # introduced for f11 and can be removed for f13: -Obsoletes: haddock < 2.4.2 -Provides: haddock = 2.4.2 +Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} +Provides: haddock = %{haddock_version}, ghc-haddock-devel = %{haddock_version} BuildRequires: ghc, happy, sed BuildRequires: gmp-devel %if %{with shared} @@ -68,25 +70,14 @@ collection of libraries, and support for various language extensions, including concurrency, exceptions, and a foreign language interface. -%if %{with prof} -%package prof -Summary: Profiling libraries for GHC -Group: Development/Libraries -Requires: %{name} = %{version}-%{release} -Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof - -%description prof -Profiling libraries for Glorious Glasgow Haskell Compilation System -(GHC). They should be installed when GHC's profiling subsystem is -needed. -%endif - %package doc Summary: Documentation for GHC Group: Development/Languages Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} +Obsoletes: ghc-haddock-doc < %{haddock_version} +Provides: ghc-haddock-doc = %{haddock_version} %description doc Preformatted documentation for the Glorious Glasgow Haskell @@ -104,6 +95,21 @@ Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). They should be installed to build standalone programs. %endif +%if %{with prof} +%package prof +Summary: Profiling libraries for GHC +Group: Development/Libraries +Requires: %{name} = %{version}-%{release} +Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof +Obsoletes: ghc-haddock-prof < %{haddock_version} +Provides: ghc-haddock-prof = %{haddock_version} + +%description prof +Profiling libraries for Glorious Glasgow Haskell Compilation System +(GHC). They should be installed when GHC's profiling subsystem is +needed. +%endif + # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} @@ -272,6 +278,9 @@ fi %endif %changelog +* Sat May 30 2009 Jens Petersen - 6.10.3-3 +- add haddock_version and use it to obsolete haddock and ghc-haddock-* + * Fri May 22 2009 Jens Petersen - 6.10.3-2 - update haddock provides and obsoletes - drop ghc-mk-pkg-install-inplace.patch: no longer needed with new 6.11 buildsys From 7532ff0904a4747cba42912ef50f274f69dc1588 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Wed, 22 Jul 2009 04:04:45 +0000 Subject: [PATCH 107/530] ghc 6.10.4 --- .cvsignore | 4 ++-- ghc.spec | 7 +++++-- sources | 4 ++-- 3 files changed, 9 insertions(+), 6 deletions(-) diff --git a/.cvsignore b/.cvsignore index 8b09f7c..4d788c5 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.10.3-src.tar.bz2 -ghc-6.10.3-src-extralibs.tar.bz2 +ghc-6.10.4-src.tar.bz2 +ghc-6.10.4-src-extralibs.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 1a8af4a..58452d8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,8 +28,8 @@ Name: ghc # part of haskell-platform -Version: 6.10.3 -Release: 3%{?dist} +Version: 6.10.4 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -278,6 +278,9 @@ fi %endif %changelog +* Tue Jul 21 2009 Bryan O'Sullivan - 6.10.4-1 +- update to 6.10.4 + * Sat May 30 2009 Jens Petersen - 6.10.3-3 - add haddock_version and use it to obsolete haddock and ghc-haddock-* diff --git a/sources b/sources index e41535f..34405f2 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -3de6a6d434c2b43def10c4cc613b265e ghc-6.10.3-src.tar.bz2 -d0fe09625556ea274df11d601c1b2a15 ghc-6.10.3-src-extralibs.tar.bz2 +167687fa582ef6702aaac24e139ec982 ghc-6.10.4-src.tar.bz2 +37ce285617d7cebabc3cf6805bdbca25 ghc-6.10.4-src-extralibs.tar.bz2 From b19d8634e1868bcc6e2d68840509fda507d20368 Mon Sep 17 00:00:00 2001 From: Jesse Keating Date: Sat, 25 Jul 2009 00:03:07 +0000 Subject: [PATCH 108/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_12_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 58452d8..fd1d251 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Name: ghc # part of haskell-platform Version: 6.10.4 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -278,6 +278,9 @@ fi %endif %changelog +* Fri Jul 24 2009 Fedora Release Engineering - 6.10.4-2 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_12_Mass_Rebuild + * Tue Jul 21 2009 Bryan O'Sullivan - 6.10.4-1 - update to 6.10.4 From 92df927325f90a4a8616ab59c43ac7caad791b1a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 28 Sep 2009 05:39:09 +0000 Subject: [PATCH 109/530] version haskell-platform note --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index fd1d251..424ffc5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ %global package_debugging 0 Name: ghc -# part of haskell-platform +# part of haskell-platform-2009.2.0.2 Version: 6.10.4 Release: 2%{?dist} Summary: Glasgow Haskell Compilation system From e6bc25d894d9720a7b6a8b0136ec573de8032275 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 1 Oct 2009 08:45:50 +0000 Subject: [PATCH 110/530] - selinux file context no longer needed in post script - (for ghc-6.12-shared) drop ld.so.conf.d files -------------------------------------------------------------- --- ghc.spec | 23 ++++++----------------- 1 file changed, 6 insertions(+), 17 deletions(-) diff --git a/ghc.spec b/ghc.spec index 424ffc5..1351a0e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -127,11 +127,11 @@ exit 0 %endif %if %{without prof} -echo "GhcLibWays=%{?with_shared:dyn}" >> mk/build.mk +echo "GhcLibWays = %{?with_shared:dyn}" >> mk/build.mk %endif %if %{with manual} -echo "XMLDocWays = html" >> mk/build.mk +echo "XMLDocWays = html" >> mk/build.mk %endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ @@ -156,11 +156,6 @@ make DESTDIR=${RPM_BUILD_ROOT} install make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif -%if %{with shared} -mkdir -p ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d -echo %{_libdir}/%{name}-%{version} > ${RPM_BUILD_ROOT}/%{_sysconfdir}/ld.so.conf.d/ghc-%{_arch}.conf -%endif - SRC_TOP=$PWD rm -f rpm-*.files ( cd $RPM_BUILD_ROOT @@ -200,9 +195,6 @@ rm testghc/* rm -rf $RPM_BUILD_ROOT %post -semanage fcontext -a -t unconfined_execmem_exec_t %{_libdir}/ghc-%{version}/ghc >/dev/null 2>&1 || : -restorecon %{_libdir}/ghc-%{version}/ghc - # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: # @@ -265,19 +257,16 @@ fi %ghost %{_docdir}/%{name}/libraries/minus.gif %ghost %{_docdir}/%{name}/libraries/plus.gif -%if %{with shared} -%files libs -%defattr(-,root,root,-) -%{_sysconfdir}/ld.so.conf.d/ghc-%{_arch}.conf -%{_libdir}/libHS*-ghc%{version}.so -%endif - %if %{with prof} %files prof -f rpm-prof.files %defattr(-,root,root,-) %endif %changelog +* Thu Oct 1 2009 Jens Petersen +- selinux file context no longer needed in post script +- (for ghc-6.12-shared) drop ld.so.conf.d files + * Fri Jul 24 2009 Fedora Release Engineering - 6.10.4-2 - Rebuilt for https://fedoraproject.org/wiki/Fedora_12_Mass_Rebuild From 41ceb8a529aae54d5fd17ab99ee1c09bec3980e4 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 12 Oct 2009 01:06:41 +0000 Subject: [PATCH 111/530] First attempt at GHC 6.12 RC 1 --- .cvsignore | 3 +-- ghc.spec | 14 ++++++-------- sources | 3 +-- 3 files changed, 8 insertions(+), 12 deletions(-) diff --git a/.cvsignore b/.cvsignore index 4d788c5..d8931b3 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1 @@ -ghc-6.10.4-src.tar.bz2 -ghc-6.10.4-src-extralibs.tar.bz2 +ghc-6.12.0.20091010-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 1351a0e..e6cd2dc 100644 --- a/ghc.spec +++ b/ghc.spec @@ -3,8 +3,6 @@ %bcond_without prof # build users_guide, etc %bcond_without manual -# include extralibs -%bcond_without extralibs # experimental ## shared libraries support available in ghc >= 6.11 @@ -28,17 +26,14 @@ Name: ghc # part of haskell-platform-2009.2.0.2 -Version: 6.10.4 -Release: 2%{?dist} +Version: 6.12.0.20091010 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 -%if %{with extralibs} -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 -%endif URL: http://haskell.org/ghc/ Requires: gcc, gmp-devel Requires(post): policycoreutils @@ -114,7 +109,7 @@ needed. %global debug_package %{nil} %prep -%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} +%setup -q -n %{name}-%{version} %build # hack for building a local test package quickly from a prebuilt tree @@ -263,6 +258,9 @@ fi %endif %changelog +* Sun Oct 11 2009 Bryan O'Sullivan - 6.12.0.20091010-1 +- Update to 6.12 RC 1 + * Thu Oct 1 2009 Jens Petersen - selinux file context no longer needed in post script - (for ghc-6.12-shared) drop ld.so.conf.d files diff --git a/sources b/sources index 34405f2..b8714e6 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -167687fa582ef6702aaac24e139ec982 ghc-6.10.4-src.tar.bz2 -37ce285617d7cebabc3cf6805bdbca25 ghc-6.10.4-src-extralibs.tar.bz2 +5ca685d5fc1c1d6924656a092f4d9b34 ghc-6.12.0.20091010-src.tar.bz2 From be50ea68e1b00690426b8f3c31352235282ae5ba Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 12 Oct 2009 01:18:42 +0000 Subject: [PATCH 112/530] Correct the version of the embedded Haddock --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index e6cd2dc..38c6a66 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ ## include colored html src %bcond_with hscolour -%global haddock_version 2.4.2 +%global haddock_version 2.5.0 # Fixing packaging problems can be a tremendous pain because it # generally requires a complete rebuild, which takes hours. To offset From 64a92f34b6c62c714b19740c64fbcb35d461ff23 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 12 Oct 2009 02:48:15 +0000 Subject: [PATCH 113/530] Figure out how to install docs --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 38c6a66..04d5a74 100644 --- a/ghc.spec +++ b/ghc.spec @@ -139,7 +139,7 @@ echo "XMLDocWays = html" >> mk/build.mk make %{_smp_mflags} %if %{with manual} -make %{_smp_mflags} html +echo XXX no longer supported - make %{_smp_mflags} html %endif %install @@ -148,7 +148,7 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install %if %{with manual} -make DESTDIR=${RPM_BUILD_ROOT} install-docs +echo XXX unnecessary make DESTDIR=${RPM_BUILD_ROOT} install-docs %endif SRC_TOP=$PWD From 7320d2d2ffd9d77decfd24886635e62fb56c0c41 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Mon, 12 Oct 2009 03:58:22 +0000 Subject: [PATCH 114/530] Build fixes --- ghc.spec | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 04d5a74..79d17a8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,10 +27,10 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: -ExclusiveArch: %{ix86} x86_64 ppc alpha +ExclusiveArch: %{ix86} x86_64 alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -42,7 +42,7 @@ Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version}, ghc-haddock-devel = %{haddock_version} -BuildRequires: ghc, happy, sed +BuildRequires: ghc, happy, sed, ncurses-devel BuildRequires: gmp-devel %if %{with shared} # not sure if this is actually needed @@ -258,6 +258,10 @@ fi %endif %changelog +* Sun Oct 11 2009 Bryan O'Sullivan - 6.12.0.20091010-2 +- disable ppc for now (seems unsupported) +- buildreq ncurses-devel + * Sun Oct 11 2009 Bryan O'Sullivan - 6.12.0.20091010-1 - Update to 6.12 RC 1 From fa36f01e95d95c1550c70165d5da442e5f917371 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 02:59:15 +0000 Subject: [PATCH 115/530] fix %check --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 79d17a8..c3809d2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -178,11 +178,11 @@ done rm -rf testghc mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs -ghc/stage2-inplace/ghc testghc/foo.hs -o testghc/foo +inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs -ghc/stage2-inplace/ghc testghc/foo.hs -o testghc/foo -O2 +inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* @@ -258,6 +258,9 @@ fi %endif %changelog +* Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-3 +- fix %check + * Sun Oct 11 2009 Bryan O'Sullivan - 6.12.0.20091010-2 - disable ppc for now (seems unsupported) - buildreq ncurses-devel From 36c509220a05d14ba8260cc0b9176248a446dfc2 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 02:59:48 +0000 Subject: [PATCH 116/530] Bump release --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c3809d2..ca7ca65 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 alpha From 3da47cd87b0a953ca7f857f5c5356fc4b11dba13 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 03:36:38 +0000 Subject: [PATCH 117/530] Try to install man pages --- ghc.spec | 8 +++++--- 1 file changed, 5 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index ca7ca65..b08c5f9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -148,8 +148,9 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install %if %{with manual} -echo XXX unnecessary make DESTDIR=${RPM_BUILD_ROOT} install-docs +make -C docs DESTDIR=${RPM_BUILD_ROOT} install-docs %endif +make -C docs/man DESTDIR=${RPM_BUILD_ROOT} install-docs SRC_TOP=$PWD rm -f rpm-*.files @@ -229,9 +230,7 @@ fi %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* -%if %{with manual} %{_mandir}/man1/ghc.* -%endif %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %files doc -f rpm-doc-dir.files @@ -258,6 +257,9 @@ fi %endif %changelog +* Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-5 +- try to install man pages + * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-3 - fix %check From 792037f8e8dbbeb74aa4c8d5e64a85704dfc1c5b Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 03:37:54 +0000 Subject: [PATCH 118/530] Bump release --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index b08c5f9..039ee84 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 alpha From 4656dedc90958db2dc34e87fbccb4418609f8133 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 04:29:19 +0000 Subject: [PATCH 119/530] Give up on man pages for now --- ghc.spec | 11 ++++++++--- 1 file changed, 8 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 039ee84..0ff644b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,7 +2,7 @@ # (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof # build users_guide, etc -%bcond_without manual +%bcond_with manual # experimental ## shared libraries support available in ghc >= 6.11 @@ -27,7 +27,7 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 alpha @@ -149,8 +149,8 @@ make DESTDIR=${RPM_BUILD_ROOT} install %if %{with manual} make -C docs DESTDIR=${RPM_BUILD_ROOT} install-docs -%endif make -C docs/man DESTDIR=${RPM_BUILD_ROOT} install-docs +%endif SRC_TOP=$PWD rm -f rpm-*.files @@ -230,7 +230,9 @@ fi %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* +%if %{with manual} %{_mandir}/man1/ghc.* +%endif %config(noreplace) %{_libdir}/ghc-%{version}/package.conf %files doc -f rpm-doc-dir.files @@ -257,6 +259,9 @@ fi %endif %changelog +* Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-6 +- give up trying to install man pages + * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-5 - try to install man pages From 30dd278708c2839ad6cff7dad74af767f2f3678c Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 04:59:42 +0000 Subject: [PATCH 120/530] package.conf.d --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0ff644b..c69257a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 5%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 alpha @@ -233,7 +233,8 @@ fi %if %{with manual} %{_mandir}/man1/ghc.* %endif -%config(noreplace) %{_libdir}/ghc-%{version}/package.conf +%dir %{_libdir}/ghc-%{version}/package.conf.d +%config(noreplace) %{_libdir}/ghc-%{version}/package.conf.d/* %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) @@ -259,6 +260,9 @@ fi %endif %changelog +* Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-7 +- fix package.conf stuff + * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-6 - give up trying to install man pages From b3f5839a6048bfbae5a06c9a4d944573a6421526 Mon Sep 17 00:00:00 2001 From: Bryan O'Sullivan Date: Fri, 13 Nov 2009 07:06:41 +0000 Subject: [PATCH 121/530] Comprehensive attempts at packaging fixes --- ghc.spec | 60 +++++++++++++++++++++----------------------------------- 1 file changed, 22 insertions(+), 38 deletions(-) diff --git a/ghc.spec b/ghc.spec index c69257a..9d464a0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,8 +1,6 @@ # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof -# build users_guide, etc -%bcond_with manual # experimental ## shared libraries support available in ghc >= 6.11 @@ -27,7 +25,7 @@ Name: ghc # part of haskell-platform-2009.2.0.2 Version: 6.12.0.20091010 -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 alpha @@ -42,15 +40,12 @@ Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version}, ghc-haddock-devel = %{haddock_version} -BuildRequires: ghc, happy, sed, ncurses-devel +BuildRequires: ghc, happy, sed, ncurses-devel, libxslt, docbook-style-xsl BuildRequires: gmp-devel %if %{with shared} # not sure if this is actually needed BuildRequires: libffi-devel %endif -%if %{with manual} -BuildRequires: libxslt, docbook-style-xsl -%endif %if %{with hscolour} BuildRequires: hscolour %endif @@ -125,9 +120,7 @@ exit 0 echo "GhcLibWays = %{?with_shared:dyn}" >> mk/build.mk %endif -%if %{with manual} echo "XMLDocWays = html" >> mk/build.mk -%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ @@ -138,25 +131,18 @@ echo "XMLDocWays = html" >> mk/build.mk make %{_smp_mflags} -%if %{with manual} -echo XXX no longer supported - make %{_smp_mflags} html -%endif - %install rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -%if %{with manual} -make -C docs DESTDIR=${RPM_BUILD_ROOT} install-docs -make -C docs/man DESTDIR=${RPM_BUILD_ROOT} install-docs -%endif +cp libraries/gen_contents_index ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html/libraries SRC_TOP=$PWD rm -f rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf*' -fprint $SRC_TOP/rpm-lib.files \) - find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files + find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf.d' -fprint $SRC_TOP/rpm-lib.files \) + find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files ) # make paths absolute (filter "./usr" to "/usr") @@ -224,35 +210,30 @@ fi %posttrans doc # (posttrans to make sure any old documentation has been removed first) -( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : +( cd %{_docdir}/ghc/html/libraries && ./gen_contents_index ) || : %files -f rpm-base.files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* -%if %{with manual} -%{_mandir}/man1/ghc.* -%endif %dir %{_libdir}/ghc-%{version}/package.conf.d %config(noreplace) %{_libdir}/ghc-%{version}/package.conf.d/* %files doc -f rpm-doc-dir.files %defattr(-,root,root,-) -%dir %{_docdir}/%{name} -%{_docdir}/%{name}/LICENSE -%if %{with manual} -%{_docdir}/%{name}/index.html -%endif -%{_docdir}/%{name}/libraries/gen_contents_index -%{_docdir}/%{name}/libraries/prologue.txt -%dir %{_docdir}/%{name}/libraries -%ghost %{_docdir}/%{name}/libraries/doc-index.html -%ghost %{_docdir}/%{name}/libraries/haddock.css -%ghost %{_docdir}/%{name}/libraries/haddock-util.js -%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/libraries/index.html -%ghost %{_docdir}/%{name}/libraries/minus.gif -%ghost %{_docdir}/%{name}/libraries/plus.gif +%{_docdir}/%{name}/html/index.html +%{_docdir}/%{name}/html/libraries/gen_contents_index +%dir %{_docdir}/%{name}/html/libraries +%doc %{_docdir}/%{name}/html/libraries/hscolour.css +%ghost %{_docdir}/%{name}/html/libraries/doc-index*.html +%ghost %{_docdir}/%{name}/html/libraries/haddock.css +%ghost %{_docdir}/%{name}/html/libraries/haddock-util.js +%ghost %{_docdir}/%{name}/html/libraries/haskell_icon.gif +%ghost %{_docdir}/%{name}/html/libraries/frames.html +%ghost %{_docdir}/%{name}/html/libraries/index.html +%ghost %{_docdir}/%{name}/html/libraries/index-frames.html +%ghost %{_docdir}/%{name}/html/libraries/minus.gif +%ghost %{_docdir}/%{name}/html/libraries/plus.gif %if %{with prof} %files prof -f rpm-prof.files @@ -260,6 +241,9 @@ fi %endif %changelog +* Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-8 +- comprehensive attempts at packaging fixes + * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-7 - fix package.conf stuff From 4b82adefe43d8b3ca8a1cf21d0f165733b2e7210 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Nov 2009 12:43:54 +0000 Subject: [PATCH 122/530] - update to 6.12.1 rc2 - build shared libs, woohoo! and package in standalone libs subpackage - add bcond for manual and extralibs - reenable ppc secondary arch - don't provide ghc-haddock-* - no longer need BR ncurses-devel or post policycoreutils requires - add vanilla v to GhcLibWays when building without prof - handle without hscolour - can't smp make currently - lots of filelist fixes for handling shared libs - run ghc-pkg recache posttrans - no need to install gen_contents_index by hand --- .cvsignore | 2 +- ghc.spec | 128 ++++++++++++++++++++++++++++++++--------------------- sources | 2 +- 3 files changed, 80 insertions(+), 52 deletions(-) diff --git a/.cvsignore b/.cvsignore index d8931b3..e542a2c 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1 @@ -ghc-6.12.0.20091010-src.tar.bz2 +ghc-6.12.0.20091121-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 9d464a0..0d3fa97 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,11 +1,14 @@ # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof - -# experimental -## shared libraries support available in ghc >= 6.11 -%bcond_with shared -## include colored html src +# build users_guide, etc +%bcond_without manual +# include extralibs +%bcond_with extralibs + +# experimental shared libraries support available in ghc-6.12 +%bcond_without shared +# include colored html src %bcond_with hscolour %global haddock_version 2.5.0 @@ -23,28 +26,34 @@ %global package_debugging 0 Name: ghc -# part of haskell-platform-2009.2.0.2 -Version: 6.12.0.20091010 -Release: 8%{?dist} +# break of haskell-platform-2009.2.0.2 +Version: 6.12.0.20091121 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: -ExclusiveArch: %{ix86} x86_64 alpha +ExclusiveArch: %{ix86} x86_64 ppc alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +%if %{with extralibs} +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 +%endif URL: http://haskell.org/ghc/ -Requires: gcc, gmp-devel -Requires(post): policycoreutils BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} -Provides: haddock = %{haddock_version}, ghc-haddock-devel = %{haddock_version} -BuildRequires: ghc, happy, sed, ncurses-devel, libxslt, docbook-style-xsl +Provides: haddock = %{haddock_version} +Requires: gcc, gmp-devel +BuildRequires: ghc, happy, sed BuildRequires: gmp-devel %if %{with shared} -# not sure if this is actually needed +# not sure if this is actually needed: BuildRequires: libffi-devel +Requires: %{name}-libs = %{version}-%{release} +%endif +%if %{with manual} +BuildRequires: libxslt, docbook-style-xsl %endif %if %{with hscolour} BuildRequires: hscolour @@ -67,22 +76,19 @@ Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} Obsoletes: ghc-haddock-doc < %{haddock_version} -Provides: ghc-haddock-doc = %{haddock_version} %description doc -Preformatted documentation for the Glorious Glasgow Haskell -Compilation System (GHC) and its libraries. It should be installed if -you like to have local access to the documentation in HTML format. +Preformatted documentation for the Glorious Glasgow Haskell Compilation System +(GHC) and its libraries. It should be installed if you like to have local +access to the documentation in HTML format. %if %{with shared} %package libs Summary: Shared libraries for GHC Group: Development/Libraries -Requires: %{name} = %{version}-%{release} %description libs -Shared libraries for Glorious Glasgow Haskell Compilation System -(GHC). They should be installed to build standalone programs. +Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). %endif %if %{with prof} @@ -92,19 +98,17 @@ Group: Development/Libraries Requires: %{name} = %{version}-%{release} Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof Obsoletes: ghc-haddock-prof < %{haddock_version} -Provides: ghc-haddock-prof = %{haddock_version} %description prof -Profiling libraries for Glorious Glasgow Haskell Compilation System -(GHC). They should be installed when GHC's profiling subsystem is -needed. +Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). +They should be installed when GHC's profiling subsystem is needed. %endif # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} %prep -%setup -q -n %{name}-%{version} +%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %build # hack for building a local test package quickly from a prebuilt tree @@ -117,10 +121,17 @@ exit 0 %endif %if %{without prof} -echo "GhcLibWays = %{?with_shared:dyn}" >> mk/build.mk +echo "GhcLibWays = v %{?with_shared:dyn}" >> mk/build.mk %endif -echo "XMLDocWays = html" >> mk/build.mk +# so where is the switch? +%if %{with manual} +#echo "XMLDocWays = html" >> mk/build.mk +%endif + +%if %{without hscolour} +echo "HSCOLOUR_SRCS = NO" >> mk/build.mk +%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ @@ -136,19 +147,20 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -cp libraries/gen_contents_index ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html/libraries - SRC_TOP=$PWD rm -f rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} \( -type d -fprintf $SRC_TOP/rpm-dir.files "%%%%dir %%p\n" \) -o \( -type f \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( -not -name 'package.conf.d' -fprint $SRC_TOP/rpm-lib.files \) - find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files + find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" + find .%{_libdir}/%{name}-%{version} -type d -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" + find .%{_libdir}/%{name}-%{version} \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) + find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc.files ) # make paths absolute (filter "./usr" to "/usr") sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files -cat rpm-dir.files rpm-lib.files > rpm-base.files +cat rpm-lib-dir.files rpm-lib.files > rpm-libs.files +cat rpm-dev-dir.files rpm-base.files > rpm-ghc.files # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -194,53 +206,69 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 -%if %{with shared} -%post libs -p /sbin/ldconfig -%endif - %preun if [ "$1" = 0 ]; then update-alternatives --remove runhaskell %{_bindir}/runghc update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi -%if %{with shared} -%postun libs -p /sbin/ldconfig -%endif +%posttrans +ghc-pkg recache %posttrans doc # (posttrans to make sure any old documentation has been removed first) ( cd %{_docdir}/ghc/html/libraries && ./gen_contents_index ) || : -%files -f rpm-base.files +%files -f rpm-ghc.files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* -%dir %{_libdir}/ghc-%{version}/package.conf.d -%config(noreplace) %{_libdir}/ghc-%{version}/package.conf.d/* +%config(noreplace) %{_libdir}/%{name}-%{version}/package.conf.d/package.cache +%if %{with manual} +#%{_mandir}/man1/ghc.* +%endif -%files doc -f rpm-doc-dir.files +%files doc -f rpm-doc.files %defattr(-,root,root,-) -%{_docdir}/%{name}/html/index.html -%{_docdir}/%{name}/html/libraries/gen_contents_index %dir %{_docdir}/%{name}/html/libraries -%doc %{_docdir}/%{name}/html/libraries/hscolour.css +%{_docdir}/%{name}/html/libraries/frames.html +%{_docdir}/%{name}/html/libraries/gen_contents_index +%{_docdir}/%{name}/html/libraries/hscolour.css +%{_docdir}/%{name}/html/libraries/prologue.txt +%{_docdir}/%{name}/html/index.html %ghost %{_docdir}/%{name}/html/libraries/doc-index*.html %ghost %{_docdir}/%{name}/html/libraries/haddock.css %ghost %{_docdir}/%{name}/html/libraries/haddock-util.js %ghost %{_docdir}/%{name}/html/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/html/libraries/frames.html -%ghost %{_docdir}/%{name}/html/libraries/index.html -%ghost %{_docdir}/%{name}/html/libraries/index-frames.html +%ghost %{_docdir}/%{name}/html/libraries/index*.html %ghost %{_docdir}/%{name}/html/libraries/minus.gif %ghost %{_docdir}/%{name}/html/libraries/plus.gif +%if %{with shared} +%files libs -f rpm-libs.files +%defattr(-,root,root,-) +%endif + %if %{with prof} %files prof -f rpm-prof.files %defattr(-,root,root,-) %endif %changelog +* Wed Nov 18 2009 Jens Petersen - 6.12.0.20091121-1 +- update to 6.12.1 rc2 +- build shared libs, yay! and package in standalone libs subpackage +- add bcond for manual and extralibs +- reenable ppc secondary arch +- don't provide ghc-haddock-* +- no longer need BR ncurses-devel or post policycoreutils requires +- add vanilla v to GhcLibWays when building without prof +- handle without hscolour +- can't smp make currently +- lots of filelist fixes for handling shared libs +- run ghc-pkg recache posttrans +- no need to install gen_contents_index by hand + * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-8 - comprehensive attempts at packaging fixes diff --git a/sources b/sources index b8714e6..f5a876a 100644 --- a/sources +++ b/sources @@ -1 +1 @@ -5ca685d5fc1c1d6924656a092f4d9b34 ghc-6.12.0.20091010-src.tar.bz2 +198ccfaabc251e7e01578d6a143f55cf ghc-6.12.0.20091121-src.tar.bz2 From 26fcbdc18a5b876d89b2ea5c973ad53bb8714f5e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Nov 2009 13:02:08 +0000 Subject: [PATCH 123/530] ok I guess BR ncurses-devel should stay --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0d3fa97..5b53c6d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -46,7 +46,7 @@ Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version} Requires: gcc, gmp-devel BuildRequires: ghc, happy, sed -BuildRequires: gmp-devel +BuildRequires: gmp-devel, ncurses-devel %if %{with shared} # not sure if this is actually needed: BuildRequires: libffi-devel @@ -261,7 +261,7 @@ ghc-pkg recache - add bcond for manual and extralibs - reenable ppc secondary arch - don't provide ghc-haddock-* -- no longer need BR ncurses-devel or post policycoreutils requires +- remove obsoltete post requires policycoreutils - add vanilla v to GhcLibWays when building without prof - handle without hscolour - can't smp make currently From 381aca137f9db8d6d61947f4e3731cf30a258187 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Nov 2009 13:40:42 +0000 Subject: [PATCH 124/530] manpage is back --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5b53c6d..a3d78da 100644 --- a/ghc.spec +++ b/ghc.spec @@ -225,7 +225,7 @@ ghc-pkg recache %{_bindir}/* %config(noreplace) %{_libdir}/%{name}-%{version}/package.conf.d/package.cache %if %{with manual} -#%{_mandir}/man1/ghc.* +%{_mandir}/man1/ghc.* %endif %files doc -f rpm-doc.files @@ -268,6 +268,7 @@ ghc-pkg recache - lots of filelist fixes for handling shared libs - run ghc-pkg recache posttrans - no need to install gen_contents_index by hand +- manpage is back * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-8 - comprehensive attempts at packaging fixes From e3475b0683837950e870eab08336da327ea0781a Mon Sep 17 00:00:00 2001 From: Bill Nottingham Date: Wed, 25 Nov 2009 23:19:24 +0000 Subject: [PATCH 125/530] Fix typo that causes a failure to update the common directory. (releng #2781) --- Makefile | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Makefile b/Makefile index e685c66..8c346a3 100644 --- a/Makefile +++ b/Makefile @@ -4,7 +4,7 @@ NAME := ghc SPECFILE = $(NAME).spec define find-makefile-common -for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done +for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$d/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done endef MAKEFILE_COMMON := $(shell $(find-makefile-common)) From f673bd89faaf1036e62086a33fe360537f048b5a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 11 Dec 2009 18:40:16 +0000 Subject: [PATCH 126/530] - update to ghc-6.12.1-pre - separate bcond options into enabled and disabled for clarity - only enable shared for intel x86 archs (Lorenzo Villani) - add quick build profile (Lorenzo Villani) - remove package_debugging hack (use "make install-short") - drop sed BR (Lorenzo Villani) - put all build.mk config into one cat block (Lorenzo Villani) - export CFLAGS to configure (Lorenzo Villani) - add dynamic linking test to check section (thanks Lorenzo Villani) - remove old ghc66 obsoletes - subpackage huge ghc internals library (thanks Lorenzo Villani) - BR ghc-rpm-macros >= 0.3.0 - move html docs to docdir/ghc from html subdir (Lorenzo Villani) --- .cvsignore | 2 +- ghc.spec | 181 ++++++++++++++++++++++++++++++++++++----------------- sources | 2 +- 3 files changed, 127 insertions(+), 58 deletions(-) diff --git a/.cvsignore b/.cvsignore index e542a2c..7ef14bc 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1 @@ -ghc-6.12.0.20091121-src.tar.bz2 +ghc-6.12.1-src.tar.bz2 diff --git a/ghc.spec b/ghc.spec index a3d78da..2dc0276 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,34 +1,29 @@ +## default enabled options ## +# experimental shared libraries support available in ghc-6.12 for x86 +%ifarch %{ix86} x86_64 +%bcond_without shared +%endif # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof # build users_guide, etc %bcond_without manual + +## default disabled options ## # include extralibs %bcond_with extralibs - -# experimental shared libraries support available in ghc-6.12 -%bcond_without shared +# quick build profile +%bcond_with quick # include colored html src %bcond_with hscolour %global haddock_version 2.5.0 -# Fixing packaging problems can be a tremendous pain because it -# generally requires a complete rebuild, which takes hours. To offset -# the misery, do a complete build once using "rpmbuild -bc", then copy -# your built tree to a directory of the same name suffixed with -# ".built", using "cp -al". Finally, set this variable, and it will -# copy the already-built tree into place during build instead of -# actually doing the build. -# -# Obviously, this can only work if you leave the build section -# completely untouched between builds. -%global package_debugging 0 Name: ghc # break of haskell-platform-2009.2.0.2 -Version: 6.12.0.20091121 -Release: 1%{?dist} +Version: 6.12.1 +Release: 0.1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -40,13 +35,13 @@ Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs %endif URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, ghc661, ghc66, haddock09 +Obsoletes: ghc682, ghc681, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version} -Requires: gcc, gmp-devel -BuildRequires: ghc, happy, sed +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.3.0 BuildRequires: gmp-devel, ncurses-devel +Requires: gcc, gmp-devel %if %{with shared} # not sure if this is actually needed: BuildRequires: libffi-devel @@ -82,7 +77,32 @@ Preformatted documentation for the Glorious Glasgow Haskell Compilation System (GHC) and its libraries. It should be installed if you like to have local access to the documentation in HTML format. +%package ghc-doc +Summary: Documentation for the ghc internals library +Group: Development/Languages +Requires(posttrans): %{name} = %{version}-%{release} + +%description ghc-doc +Documentation for the ghc internals library. + +%package ghc-devel +Summary: Development files for ghc internals +Group: Development/Libraries +%if %{with shared} +Requires: %{name}-ghc = %{version}-%{release} +%endif + +%description ghc-devel +Development files for the ghc internals library. + %if %{with shared} +%package ghc +Summary: GHC internals library +Group: Development/Libraries + +%description ghc +Library to access internals of the Glasgow Haskell Compilation System. + %package libs Summary: Shared libraries for GHC Group: Development/Libraries @@ -96,12 +116,21 @@ Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). Summary: Profiling libraries for GHC Group: Development/Libraries Requires: %{name} = %{version}-%{release} -Obsoletes: ghc682-prof, ghc681-prof, ghc661-prof, ghc66-prof +Obsoletes: ghc682-prof, ghc681-prof Obsoletes: ghc-haddock-prof < %{haddock_version} %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). They should be installed when GHC's profiling subsystem is needed. + +%package ghc-prof +Summary: Profiling libraries for the ghc internals library +Group: Development/Libraries +Requires: %{name}-ghc-devel = %{version}-%{release} +Requires: %{name}-prof = %{version}-%{release} + +%description ghc-prof +Profiling libraries for the ghc internals library. %endif # the debuginfo subpackage is currently empty anyway, so don't generate it @@ -111,28 +140,27 @@ They should be installed when GHC's profiling subsystem is needed. %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %build -# hack for building a local test package quickly from a prebuilt tree -%if %{package_debugging} -pushd .. -rm -rf %{name}-%{version} -cp -al %{name}-%{version}.built %{name}-%{version} -popd -exit 0 -%endif - +cat > mk/build.mk << EOF %if %{without prof} -echo "GhcLibWays = v %{?with_shared:dyn}" >> mk/build.mk +GhcLibWays = v %{?with_shared:dyn} %endif - -# so where is the switch? -%if %{with manual} -#echo "XMLDocWays = html" >> mk/build.mk +%if %{without manual} +HADDOCK_DOCS = NO +BUILD_DOCBOOK_HTML = NO +%endif +%if %{with quick} +SRC_HC_OPTS = -H64m -O0 -fasm +GhcStage1HcOpts = -O -fasm +GhcStage2HcOpts = -O0 -fasm +GhcLibHcOpts = -O0 -fasm +SplitObjs = NO %endif - %if %{without hscolour} -echo "HSCOLOUR_SRCS = NO" >> mk/build.mk +HSCOLOUR_SRCS = NO %endif +EOF +export CFLAGS="${CFLAGS:-%optflags}" ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -144,16 +172,20 @@ make %{_smp_mflags} %install rm -rf $RPM_BUILD_ROOT - make DESTDIR=${RPM_BUILD_ROOT} install +# hack around apparent html/ hardcoding +mv ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html{,-tmp} +mv ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp/* ${RPM_BUILD_ROOT}%{_docdir}/%{name} +rmdir ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp + SRC_TOP=$PWD rm -f rpm-*.files ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" - find .%{_libdir}/%{name}-%{version} -type d -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" - find .%{_libdir}/%{name}-%{version} \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) - find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc.files + find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' ! -name 'ghc-%{version}' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" + find .%{_libdir}/%{name}-%{version} -type d \( -path 'ghc-%{version}' -prune -o -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) + find .%{_libdir}/%{name}-%{version} \( -path 'ghc-%{version}' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) + find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name 'ghc-%{version}' ! -name src > $SRC_TOP/rpm-doc.files ) # make paths absolute (filter "./usr" to "/usr") @@ -162,6 +194,10 @@ sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files cat rpm-lib-dir.files rpm-lib.files > rpm-libs.files cat rpm-dev-dir.files rpm-base.files > rpm-ghc.files +# subpackage ghc library +%define ghc_version %{version} +%ghc_gen_filelists ghc-ghc %{version} + # these are handled as alternatives for i in hsc2hs runhaskell; do if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then @@ -184,6 +220,12 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* +%if %{with shared} +echo 'main = putStrLn "Foo"' > testghc/foo.hs +inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic +[ "$(testghc/foo)" = "Foo" ] +rm testghc/* +%endif %clean rm -rf $RPM_BUILD_ROOT @@ -217,7 +259,7 @@ ghc-pkg recache %posttrans doc # (posttrans to make sure any old documentation has been removed first) -( cd %{_docdir}/ghc/html/libraries && ./gen_contents_index ) || : +( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : %files -f rpm-ghc.files %defattr(-,root,root,-) @@ -230,31 +272,58 @@ ghc-pkg recache %files doc -f rpm-doc.files %defattr(-,root,root,-) -%dir %{_docdir}/%{name}/html/libraries -%{_docdir}/%{name}/html/libraries/frames.html -%{_docdir}/%{name}/html/libraries/gen_contents_index -%{_docdir}/%{name}/html/libraries/hscolour.css -%{_docdir}/%{name}/html/libraries/prologue.txt -%{_docdir}/%{name}/html/index.html -%ghost %{_docdir}/%{name}/html/libraries/doc-index*.html -%ghost %{_docdir}/%{name}/html/libraries/haddock.css -%ghost %{_docdir}/%{name}/html/libraries/haddock-util.js -%ghost %{_docdir}/%{name}/html/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/html/libraries/index*.html -%ghost %{_docdir}/%{name}/html/libraries/minus.gif -%ghost %{_docdir}/%{name}/html/libraries/plus.gif +%dir %{_docdir}/%{name}/libraries +%{_docdir}/%{name}/libraries/frames.html +%{_docdir}/%{name}/libraries/gen_contents_index +%{_docdir}/%{name}/libraries/hscolour.css +%{_docdir}/%{name}/libraries/prologue.txt +%{_docdir}/%{name}/index.html +%ghost %{_docdir}/%{name}/libraries/doc-index*.html +%ghost %{_docdir}/%{name}/libraries/haddock.css +%ghost %{_docdir}/%{name}/libraries/haddock-util.js +%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif +%ghost %{_docdir}/%{name}/libraries/index*.html +%ghost %{_docdir}/%{name}/libraries/minus.gif +%ghost %{_docdir}/%{name}/libraries/plus.gif %if %{with shared} %files libs -f rpm-libs.files %defattr(-,root,root,-) + +%files ghc -f ghc-ghc.files +%defattr(-,root,root,-) %endif +%files ghc-devel -f ghc-ghc-devel.files +%defattr(-,root,root,-) + +%files ghc-doc -f ghc-ghc-doc.files +%defattr(-,root,root,-) + %if %{with prof} %files prof -f rpm-prof.files %defattr(-,root,root,-) + +%files ghc-prof -f ghc-ghc-prof.files +%defattr(-,root,root,-) %endif %changelog +* Fri Dec 11 2009 Jens Petersen - 6.12.1-0.1 +- update to ghc-6.12.1-pre +- separate bcond options into enabled and disabled for clarity +- only enable shared for intel x86 archs (Lorenzo Villani) +- add quick build profile (Lorenzo Villani) +- remove package_debugging hack (use "make install-short") +- drop sed BR (Lorenzo Villani) +- put all build.mk config into one cat block (Lorenzo Villani) +- export CFLAGS to configure (Lorenzo Villani) +- add dynamic linking test to check section (thanks Lorenzo Villani) +- remove old ghc66 obsoletes +- subpackage huge ghc internals library (thanks Lorenzo Villani) + - BR ghc-rpm-macros >= 0.3.0 +- move html docs to docdir/ghc from html subdir (Lorenzo Villani) + * Wed Nov 18 2009 Jens Petersen - 6.12.0.20091121-1 - update to 6.12.1 rc2 - build shared libs, yay! and package in standalone libs subpackage @@ -668,7 +737,7 @@ ghc-pkg recache * Fri Feb 26 1999 Manuel Chakravarty - modified for GHC 4.02 -* Thu Dec 24 1998 Zoltan Vorosbaranyi +* Thu Dec 24 1998 Zoltan Vorosbaranyi - added BuildRoot - files located in /usr/local/bin, /usr/local/lib moved to /usr/bin, /usr/lib diff --git a/sources b/sources index f5a876a..613cc7b 100644 --- a/sources +++ b/sources @@ -1 +1 @@ -198ccfaabc251e7e01578d6a143f55cf ghc-6.12.0.20091121-src.tar.bz2 +3a2b23f29013605f721ebdfc29de9c92 ghc-6.12.1-src.tar.bz2 From b467c90b76cb4e0241576862d6b05a3a339674c6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 11 Dec 2009 19:17:18 +0000 Subject: [PATCH 127/530] disable smp build for now: broken for 8 cpus at least --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 2dc0276..5a71fc8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -168,7 +168,9 @@ export CFLAGS="${CFLAGS:-%optflags}" --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ %{?with_shared:--enable-shared} -make %{_smp_mflags} +# 8 cpus seems to break build +#make %{_smp_mflags} +make %install rm -rf $RPM_BUILD_ROOT @@ -323,6 +325,7 @@ ghc-pkg recache - subpackage huge ghc internals library (thanks Lorenzo Villani) - BR ghc-rpm-macros >= 0.3.0 - move html docs to docdir/ghc from html subdir (Lorenzo Villani) +- disable smp build for now: broken for 8 cpus at least * Wed Nov 18 2009 Jens Petersen - 6.12.0.20091121-1 - update to 6.12.1 rc2 From 60aa61e3bc133a983abeef1101de74c6c501c1a2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 12 Dec 2009 03:59:37 +0000 Subject: [PATCH 128/530] - remove redundant mingw and perl from ghc-tarballs/ - fix exclusion of ghc internals lib from base packages with -mindepth - rename the final file lists to PKGNAME.files for clarity --- ghc.spec | 34 ++++++++++++++++++++++------------ 1 file changed, 22 insertions(+), 12 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5a71fc8..bb1098e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -23,7 +23,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -Release: 0.1%{?dist} +Release: 0.2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -139,6 +139,9 @@ Profiling libraries for the ghc internals library. %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} +# make sure we don't use these +rm -r ghc-tarballs/{mingw,perl} + %build cat > mk/build.mk << EOF %if %{without prof} @@ -182,19 +185,20 @@ mv ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp/* ${RPM_BUILD_ROOT}%{_docdir}/%{ rmdir ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp SRC_TOP=$PWD -rm -f rpm-*.files +#rm -f rpm-*.files +# exclude ghc library since it is subpackaged separately ( cd $RPM_BUILD_ROOT find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' ! -name 'ghc-%{version}' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" - find .%{_libdir}/%{name}-%{version} -type d \( -path 'ghc-%{version}' -prune -o -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) - find .%{_libdir}/%{name}-%{version} \( -path 'ghc-%{version}' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/rpm-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) - find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name 'ghc-%{version}' ! -name src > $SRC_TOP/rpm-doc.files + find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -name 'ghc-%{version}' -prune -o -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) + find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'ghc-%{version}' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) + find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name 'ghc-%{version}' ! -name src > $SRC_TOP/ghc-doc.files ) # make paths absolute (filter "./usr" to "/usr") -sed -i -e "s|\.%{_prefix}|%{_prefix}|" rpm-*.files +sed -i -e "s|\.%{_prefix}|%{_prefix}|" *.files -cat rpm-lib-dir.files rpm-lib.files > rpm-libs.files -cat rpm-dev-dir.files rpm-base.files > rpm-ghc.files +cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files +cat rpm-dev-dir.files rpm-base.files > ghc.files # subpackage ghc library %define ghc_version %{version} @@ -263,16 +267,17 @@ ghc-pkg recache # (posttrans to make sure any old documentation has been removed first) ( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : -%files -f rpm-ghc.files +%files -f ghc.files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* +%dir %{_libdir}/%{name}-%{version} %config(noreplace) %{_libdir}/%{name}-%{version}/package.conf.d/package.cache %if %{with manual} %{_mandir}/man1/ghc.* %endif -%files doc -f rpm-doc.files +%files doc -f ghc-doc.files %defattr(-,root,root,-) %dir %{_docdir}/%{name}/libraries %{_docdir}/%{name}/libraries/frames.html @@ -289,7 +294,7 @@ ghc-pkg recache %ghost %{_docdir}/%{name}/libraries/plus.gif %if %{with shared} -%files libs -f rpm-libs.files +%files libs -f ghc-libs.files %defattr(-,root,root,-) %files ghc -f ghc-ghc.files @@ -303,7 +308,7 @@ ghc-pkg recache %defattr(-,root,root,-) %if %{with prof} -%files prof -f rpm-prof.files +%files prof -f ghc-prof.files %defattr(-,root,root,-) %files ghc-prof -f ghc-ghc-prof.files @@ -311,6 +316,11 @@ ghc-pkg recache %endif %changelog +* Sat Dec 12 2009 Jens Petersen - 6.12.1-0.2 +- remove redundant mingw and perl from ghc-tarballs/ +- fix exclusion of ghc internals lib from base packages with -mindepth +- rename the final file lists to PKGNAME.files for clarity + * Fri Dec 11 2009 Jens Petersen - 6.12.1-0.1 - update to ghc-6.12.1-pre - separate bcond options into enabled and disabled for clarity From feffa9307913fbc7ab9f10f32aae8d70e289dcac Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 12 Dec 2009 10:47:38 +0000 Subject: [PATCH 129/530] - exclude ghc .conf file from package.conf.d in base package - use ghc_reindex_haddock - add scripts for ghc-ghc-devel and ghc-ghc-doc - add doc bcond --- ghc.spec | 48 +++++++++++++++++++++++++++++++++++++++++------- 1 file changed, 41 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index bb1098e..d0fd611 100644 --- a/ghc.spec +++ b/ghc.spec @@ -3,10 +3,11 @@ %ifarch %{ix86} x86_64 %bcond_without shared %endif +%bcond_without doc # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) %bcond_without prof -# build users_guide, etc +# build xml manuals (users_guide, etc) %bcond_without manual ## default disabled options ## @@ -23,7 +24,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -Release: 0.2%{?dist} +Release: 0.3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -77,13 +78,17 @@ Preformatted documentation for the Glorious Glasgow Haskell Compilation System (GHC) and its libraries. It should be installed if you like to have local access to the documentation in HTML format. +%if %{with doc} %package ghc-doc Summary: Documentation for the ghc internals library Group: Development/Languages -Requires(posttrans): %{name} = %{version}-%{release} +Requires: %{name}-doc = %{version} +Requires(post): %{name}-doc = %{version} +Requires(postun): %{name}-doc = %{version} %description ghc-doc Documentation for the ghc internals library. +%endif %package ghc-devel Summary: Development files for ghc internals @@ -147,8 +152,10 @@ cat > mk/build.mk << EOF %if %{without prof} GhcLibWays = v %{?with_shared:dyn} %endif -%if %{without manual} +%if %{without doc} HADDOCK_DOCS = NO +%endif +%if %{without manual} BUILD_DOCBOOK_HTML = NO %endif %if %{with quick} @@ -190,7 +197,7 @@ SRC_TOP=$PWD ( cd $RPM_BUILD_ROOT find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' ! -name 'ghc-%{version}' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -name 'ghc-%{version}' -prune -o -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) - find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'ghc-%{version}' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) + find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'ghc-%{version}*' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name 'ghc-%{version}' ! -name src > $SRC_TOP/ghc-doc.files ) @@ -261,11 +268,28 @@ if [ "$1" = 0 ]; then fi %posttrans +# (posttrans to make sure any old libs have been removed first) +ghc-pkg recache + +%post ghc-devel +ghc-pkg recache + +%postun ghc-devel ghc-pkg recache %posttrans doc -# (posttrans to make sure any old documentation has been removed first) -( cd %{_docdir}/ghc/libraries && ./gen_contents_index ) || : +# (posttrans to make sure any old docs have been removed first) +%ghc_reindex_haddock + +%if %{with doc} +%post ghc-doc +%ghc_reindex_haddock + +%postun ghc-doc +if [ "$1" -eq 0 ] ; then + %ghc_reindex_haddock +fi +%endif %files -f ghc.files %defattr(-,root,root,-) @@ -279,6 +303,7 @@ ghc-pkg recache %files doc -f ghc-doc.files %defattr(-,root,root,-) +%if %{with doc} %dir %{_docdir}/%{name}/libraries %{_docdir}/%{name}/libraries/frames.html %{_docdir}/%{name}/libraries/gen_contents_index @@ -292,6 +317,7 @@ ghc-pkg recache %ghost %{_docdir}/%{name}/libraries/index*.html %ghost %{_docdir}/%{name}/libraries/minus.gif %ghost %{_docdir}/%{name}/libraries/plus.gif +%endif %if %{with shared} %files libs -f ghc-libs.files @@ -304,8 +330,10 @@ ghc-pkg recache %files ghc-devel -f ghc-ghc-devel.files %defattr(-,root,root,-) +%if %{with doc} %files ghc-doc -f ghc-ghc-doc.files %defattr(-,root,root,-) +%endif %if %{with prof} %files prof -f ghc-prof.files @@ -316,6 +344,12 @@ ghc-pkg recache %endif %changelog +* Sat Dec 12 2009 Jens Petersen - 6.12.1-0.3 +- exclude ghc .conf file from package.conf.d in base package +- use ghc_reindex_haddock +- add scripts for ghc-ghc-devel and ghc-ghc-doc +- add doc bcond + * Sat Dec 12 2009 Jens Petersen - 6.12.1-0.2 - remove redundant mingw and perl from ghc-tarballs/ - fix exclusion of ghc internals lib from base packages with -mindepth From bedcaee1302e8423f6ea63ab1b8535fe122c91c4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 12 Dec 2009 11:34:17 +0000 Subject: [PATCH 130/530] - add ghc-6.12.1-gen_contents_index-haddock-path.patch to adjust haddock path since we removed html/ from libraries path --- ghc-6.12.1-gen_contents_index-haddock-path.patch | 12 ++++++++++++ ghc.spec | 5 +++++ 2 files changed, 17 insertions(+) create mode 100644 ghc-6.12.1-gen_contents_index-haddock-path.patch diff --git a/ghc-6.12.1-gen_contents_index-haddock-path.patch b/ghc-6.12.1-gen_contents_index-haddock-path.patch new file mode 100644 index 0000000..d1034eb --- /dev/null +++ b/ghc-6.12.1-gen_contents_index-haddock-path.patch @@ -0,0 +1,12 @@ +diff -u ghc-6.12.1/libraries/gen_contents_index\~ ghc-6.12.1/libraries/gen_contents_index +--- ghc-6.12.1/libraries/gen_contents_index~ 2009-12-11 04:11:33.000000000 +1000 ++++ ghc-6.12.1/libraries/gen_contents_index 2009-12-12 21:08:02.000000000 +1000 +@@ -20,7 +20,7 @@ + done + ;; + *) +- HADDOCK=../../../../../bin/haddock ++ HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index + HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` + for HADDOCK_FILE in $HADDOCK_FILES diff --git a/ghc.spec b/ghc.spec index d0fd611..166f4df 100644 --- a/ghc.spec +++ b/ghc.spec @@ -54,6 +54,7 @@ BuildRequires: libxslt, docbook-style-xsl %if %{with hscolour} BuildRequires: hscolour %endif +Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -143,6 +144,8 @@ Profiling libraries for the ghc internals library. %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} +# tweak haddock path for html/libraries -> libraries +%patch1 -p1 -b .orig # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -349,6 +352,8 @@ fi - use ghc_reindex_haddock - add scripts for ghc-ghc-devel and ghc-ghc-doc - add doc bcond +- add ghc-6.12.1-gen_contents_index-haddock-path.patch to adjust haddock path + since we removed html/ from libraries path * Sat Dec 12 2009 Jens Petersen - 6.12.1-0.2 - remove redundant mingw and perl from ghc-tarballs/ From 0f975a51111ac2b855f5f1516231869da9cf9349 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 16 Dec 2009 07:58:28 +0000 Subject: [PATCH 131/530] require ghc-rpm-macros-0.3.1 and use ghc_version_override --- ghc.spec | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 166f4df..0662ef7 100644 --- a/ghc.spec +++ b/ghc.spec @@ -40,7 +40,7 @@ Obsoletes: ghc682, ghc681, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version} -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.3.0 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.3.1 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -211,7 +211,7 @@ cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files cat rpm-dev-dir.files rpm-base.files > ghc.files # subpackage ghc library -%define ghc_version %{version} +%define ghc_version_override %{version} %ghc_gen_filelists ghc-ghc %{version} # these are handled as alternatives @@ -347,13 +347,14 @@ fi %endif %changelog -* Sat Dec 12 2009 Jens Petersen - 6.12.1-0.3 +* Wed Dec 16 2009 Jens Petersen - 6.12.1-0.3 - exclude ghc .conf file from package.conf.d in base package - use ghc_reindex_haddock - add scripts for ghc-ghc-devel and ghc-ghc-doc - add doc bcond - add ghc-6.12.1-gen_contents_index-haddock-path.patch to adjust haddock path since we removed html/ from libraries path +- require ghc-rpm-macros-0.3.1 and use ghc_version_override * Sat Dec 12 2009 Jens Petersen - 6.12.1-0.2 - remove redundant mingw and perl from ghc-tarballs/ From b277f721acbc28d8dc781f223cdeb75ff213f7ba Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 16 Dec 2009 08:11:43 +0000 Subject: [PATCH 132/530] pre became 6.12.1 final --- ghc.spec | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0662ef7..14a2386 100644 --- a/ghc.spec +++ b/ghc.spec @@ -24,7 +24,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -Release: 0.3%{?dist} +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -347,7 +347,8 @@ fi %endif %changelog -* Wed Dec 16 2009 Jens Petersen - 6.12.1-0.3 +* Wed Dec 16 2009 Jens Petersen - 6.12.1-1 +- pre promoted to 6.12.1 final - exclude ghc .conf file from package.conf.d in base package - use ghc_reindex_haddock - add scripts for ghc-ghc-devel and ghc-ghc-doc From 3b5aa06c8825dc5f64db8838a168bedc022fe49e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 22 Dec 2009 09:35:43 +0000 Subject: [PATCH 133/530] add p_dyn (dynamic profiling libs) for binlib packages --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 14a2386..323d36d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -24,7 +24,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -152,9 +152,7 @@ rm -r ghc-tarballs/{mingw,perl} %build cat > mk/build.mk << EOF -%if %{without prof} -GhcLibWays = v %{?with_shared:dyn} -%endif +GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn %{?with_prof:p_dyn}} %if %{without doc} HADDOCK_DOCS = NO %endif @@ -347,6 +345,9 @@ fi %endif %changelog +* Tue Dec 22 2009 Jens Petersen - 6.12.1-2 +- add p_dyn (dynamic profiling libs) for binlib packages + * Wed Dec 16 2009 Jens Petersen - 6.12.1-1 - pre promoted to 6.12.1 final - exclude ghc .conf file from package.conf.d in base package From b21eb153ec1549b6c254f052b6aee15f62a43a88 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 10 Jan 2010 16:03:50 +0000 Subject: [PATCH 134/530] - include haskeline, mtl, and terminfo for now with ghc-6.12.1-no-filter-libs.patch - use ghc_binlibpackage, grep -v and ghc_gen_filelists to generate the library subpackages (ghc-rpm-macros-0.5.1) - always set GhcLibWays (Lorenzo Villani) - use ghcdocbasedir to revert html doc path to upstream's html/ for consistency --- ghc.spec | 155 ++++++++++++++++++++----------------------------------- 1 file changed, 55 insertions(+), 100 deletions(-) diff --git a/ghc.spec b/ghc.spec index 323d36d..6c71c30 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,6 +20,8 @@ %global haddock_version 2.5.0 +# the debuginfo subpackage is currently empty anyway, so don't generate it +%global debug_package %{nil} Name: ghc # break of haskell-platform-2009.2.0.2 @@ -40,7 +42,7 @@ Obsoletes: ghc682, ghc681, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version} -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.3.1 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.1 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -55,6 +57,7 @@ BuildRequires: libxslt, docbook-style-xsl BuildRequires: hscolour %endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch +Patch2: ghc-6.12.1-no-filter-libs.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -79,36 +82,7 @@ Preformatted documentation for the Glorious Glasgow Haskell Compilation System (GHC) and its libraries. It should be installed if you like to have local access to the documentation in HTML format. -%if %{with doc} -%package ghc-doc -Summary: Documentation for the ghc internals library -Group: Development/Languages -Requires: %{name}-doc = %{version} -Requires(post): %{name}-doc = %{version} -Requires(postun): %{name}-doc = %{version} - -%description ghc-doc -Documentation for the ghc internals library. -%endif - -%package ghc-devel -Summary: Development files for ghc internals -Group: Development/Libraries -%if %{with shared} -Requires: %{name}-ghc = %{version}-%{release} -%endif - -%description ghc-devel -Development files for the ghc internals library. - %if %{with shared} -%package ghc -Summary: GHC internals library -Group: Development/Libraries - -%description ghc -Library to access internals of the Glasgow Haskell Compilation System. - %package libs Summary: Shared libraries for GHC Group: Development/Libraries @@ -128,31 +102,33 @@ Obsoletes: ghc-haddock-prof < %{haddock_version} %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). They should be installed when GHC's profiling subsystem is needed. +%endif -%package ghc-prof -Summary: Profiling libraries for the ghc internals library -Group: Development/Libraries -Requires: %{name}-ghc-devel = %{version}-%{release} -Requires: %{name}-prof = %{version}-%{release} +%global ghc_version_override %{version} -%description ghc-prof -Profiling libraries for the ghc internals library. -%endif +%ghc_binlib_package -n ghc -# the debuginfo subpackage is currently empty anyway, so don't generate it -%global debug_package %{nil} +%ghc_binlib_package -n haskeline -v 0.6.2.1 + +%ghc_binlib_package -n mtl -v 1.1.0.2 + +%ghc_binlib_package -n terminfo -v 0.3.1.1 + +%global version %{ghc_version_override} %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} -# tweak haddock path for html/libraries -> libraries +# absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig +# install more libs +%patch2 -p1 -b .orig # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} %build cat > mk/build.mk << EOF -GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn %{?with_prof:p_dyn}} +GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn} %if %{without doc} HADDOCK_DOCS = NO %endif @@ -187,19 +163,13 @@ make rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -# hack around apparent html/ hardcoding -mv ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html{,-tmp} -mv ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp/* ${RPM_BUILD_ROOT}%{_docdir}/%{name} -rmdir ${RPM_BUILD_ROOT}%{_docdir}/%{name}/html-tmp - SRC_TOP=$PWD #rm -f rpm-*.files -# exclude ghc library since it is subpackaged separately ( cd $RPM_BUILD_ROOT - find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' ! -name 'ghc-%{version}' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" - find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -name 'ghc-%{version}' -prune -o -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) - find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'ghc-%{version}*' -prune \) -o \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) - find .%{_docdir}/%{name}/* -type d ! -name libraries ! -name 'ghc-%{version}' ! -name src > $SRC_TOP/ghc-doc.files + find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" + find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) + find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) + find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/ghc-doc.files ) # make paths absolute (filter "./usr" to "/usr") @@ -208,9 +178,20 @@ sed -i -e "s|\.%{_prefix}|%{_prefix}|" *.files cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files cat rpm-dev-dir.files rpm-base.files > ghc.files -# subpackage ghc library -%define ghc_version_override %{version} -%ghc_gen_filelists ghc-ghc %{version} +# subpackage ghc and extra libraries +sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files +sed -i -e "/ghc-%{version}-.*.conf\$/d" ghc.files +sed -i -e "/ghc-%{version}\$/d" ghc-doc.files +%ghc_gen_filelists ghc + +for pkg in haskeline-0.6.2.1 mtl-1.1.0.2 terminfo-0.3.1.1; do + sed -i -e "/ghc-%{version}\/$pkg/d" ghc.files ghc-libs.files + sed -i -e "/$pkg-.*.conf\$/d" ghc.files + sed -i -e "/$pkg\$/d" ghc-doc.files + name=$(echo $pkg | sed -e "s/\(.*\)-.*/\1/") + version=$(echo $pkg | sed -e "s/.*-\(.*\)/\1/") + %ghc_gen_filelists ${name} ${version} +done # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -272,26 +253,10 @@ fi # (posttrans to make sure any old libs have been removed first) ghc-pkg recache -%post ghc-devel -ghc-pkg recache - -%postun ghc-devel -ghc-pkg recache - %posttrans doc # (posttrans to make sure any old docs have been removed first) %ghc_reindex_haddock -%if %{with doc} -%post ghc-doc -%ghc_reindex_haddock - -%postun ghc-doc -if [ "$1" -eq 0 ] ; then - %ghc_reindex_haddock -fi -%endif - %files -f ghc.files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README @@ -305,51 +270,41 @@ fi %files doc -f ghc-doc.files %defattr(-,root,root,-) %if %{with doc} -%dir %{_docdir}/%{name}/libraries -%{_docdir}/%{name}/libraries/frames.html -%{_docdir}/%{name}/libraries/gen_contents_index -%{_docdir}/%{name}/libraries/hscolour.css -%{_docdir}/%{name}/libraries/prologue.txt -%{_docdir}/%{name}/index.html -%ghost %{_docdir}/%{name}/libraries/doc-index*.html -%ghost %{_docdir}/%{name}/libraries/haddock.css -%ghost %{_docdir}/%{name}/libraries/haddock-util.js -%ghost %{_docdir}/%{name}/libraries/haskell_icon.gif -%ghost %{_docdir}/%{name}/libraries/index*.html -%ghost %{_docdir}/%{name}/libraries/minus.gif -%ghost %{_docdir}/%{name}/libraries/plus.gif +%dir %{ghcdocbasedir}/libraries +%{ghcdocbasedir}/libraries/frames.html +%{ghcdocbasedir}/libraries/gen_contents_index +%{ghcdocbasedir}/libraries/hscolour.css +%{ghcdocbasedir}/libraries/prologue.txt +%{ghcdocbasedir}/index.html +%ghost %{ghcdocbasedir}/libraries/doc-index*.html +%ghost %{ghcdocbasedir}/libraries/haddock.css +%ghost %{ghcdocbasedir}/libraries/haddock-util.js +%ghost %{ghcdocbasedir}/libraries/haskell_icon.gif +%ghost %{ghcdocbasedir}/libraries/index*.html +%ghost %{ghcdocbasedir}/libraries/minus.gif +%ghost %{ghcdocbasedir}/libraries/plus.gif %endif %if %{with shared} %files libs -f ghc-libs.files %defattr(-,root,root,-) - -%files ghc -f ghc-ghc.files -%defattr(-,root,root,-) -%endif - -%files ghc-devel -f ghc-ghc-devel.files -%defattr(-,root,root,-) - -%if %{with doc} -%files ghc-doc -f ghc-ghc-doc.files -%defattr(-,root,root,-) %endif %if %{with prof} %files prof -f ghc-prof.files %defattr(-,root,root,-) - -%files ghc-prof -f ghc-ghc-prof.files -%defattr(-,root,root,-) %endif %changelog * Tue Dec 22 2009 Jens Petersen - 6.12.1-2 -- add p_dyn (dynamic profiling libs) for binlib packages +- add subpackages for haskeline, mtl, and terminfo for now with + ghc-6.12.1-no-filter-libs.patch: use ghc_binlibpackage, grep -v and + ghc_gen_filelists to generate the library subpackages (ghc-rpm-macros-0.5.1) +- always set GhcLibWays (Lorenzo Villani) +- use ghcdocbasedir to revert html doc path to upstream's html/ for consistency * Wed Dec 16 2009 Jens Petersen - 6.12.1-1 -- pre promoted to 6.12.1 final +- pre became 6.12.1 final - exclude ghc .conf file from package.conf.d in base package - use ghc_reindex_haddock - add scripts for ghc-ghc-devel and ghc-ghc-doc From c07a273d46828017ce7a26684bb96a6fd6cd8f7b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 10 Jan 2010 16:09:39 +0000 Subject: [PATCH 135/530] add ghc-6.12.1-no-filter-libs.patch --- ghc-6.12.1-no-filter-libs.patch | 12 ++++++++++++ 1 file changed, 12 insertions(+) create mode 100644 ghc-6.12.1-no-filter-libs.patch diff --git a/ghc-6.12.1-no-filter-libs.patch b/ghc-6.12.1-no-filter-libs.patch new file mode 100644 index 0000000..6e67baa --- /dev/null +++ b/ghc-6.12.1-no-filter-libs.patch @@ -0,0 +1,12 @@ +diff -u ghc-6.12.1/ghc.mk\~ ghc-6.12.1/ghc.mk +--- ghc-6.12.1/ghc.mk~ 2009-12-11 04:11:33.000000000 +1000 ++++ ghc-6.12.1/ghc.mk 2010-01-09 23:17:20.000000000 +1000 +@@ -846,7 +846,7 @@ + INSTALLED_GHC_PKG_REAL=$(DESTDIR)$(bindir)/ghc-pkg.exe + endif + +-INSTALLED_PACKAGES = $(filter-out haskeline mtl terminfo,$(PACKAGES)) ++INSTALLED_PACKAGES = $(PACKAGES) + HIDDEN_PACKAGES = ghc-binary + + define set_INSTALL_DISTDIR From 0fbb24d072001b301ae096aa9404bdf6b695f502 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 04:16:46 +0000 Subject: [PATCH 136/530] ghc-rpm-macros-0.5.2 fixes broken pkg_name requires for lib packages --- ghc.spec | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6c71c30..69e38fb 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,8 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -Release: 2%{?dist} +# can't be reset as long as there are versioned subpackages +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -42,7 +43,7 @@ Obsoletes: ghc682, ghc681, haddock09 # introduced for f11 and can be removed for f13: Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} Provides: haddock = %{haddock_version} -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.1 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.2 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -296,10 +297,14 @@ ghc-pkg recache %endif %changelog +* Mon Jan 11 2010 Jens Petersen - 6.12.1-3 +- ghc-rpm-macros-0.5.2 fixes broken pkg_name requires for lib packages + * Tue Dec 22 2009 Jens Petersen - 6.12.1-2 -- add subpackages for haskeline, mtl, and terminfo for now with - ghc-6.12.1-no-filter-libs.patch: use ghc_binlibpackage, grep -v and - ghc_gen_filelists to generate the library subpackages (ghc-rpm-macros-0.5.1) +- include haskeline, mtl, and terminfo for now with + ghc-6.12.1-no-filter-libs.patch +- use ghc_binlibpackage, grep -v and ghc_gen_filelists to generate + the library subpackages (ghc-rpm-macros-0.5.1) - always set GhcLibWays (Lorenzo Villani) - use ghcdocbasedir to revert html doc path to upstream's html/ for consistency From 5ada020f4ef2a5f71e7892d8a08c2a608c55a204 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 04:18:31 +0000 Subject: [PATCH 137/530] changelog tweak to say subpackages --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 69e38fb..fdd026f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -298,7 +298,7 @@ ghc-pkg recache %changelog * Mon Jan 11 2010 Jens Petersen - 6.12.1-3 -- ghc-rpm-macros-0.5.2 fixes broken pkg_name requires for lib packages +- ghc-rpm-macros-0.5.2 fixes broken pkg_name requires for lib subpackages * Tue Dec 22 2009 Jens Petersen - 6.12.1-2 - include haskeline, mtl, and terminfo for now with From b87c7b1c5dab64fdc0c6253e181ea4c0e7e27eb7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 07:42:48 +0000 Subject: [PATCH 138/530] ghc-rpm-macros-0.5.4 fixes wrong version requires between lib subpackages --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index fdd026f..768ae4e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 # can't be reset as long as there are versioned subpackages -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -297,6 +297,9 @@ ghc-pkg recache %endif %changelog +* Mon Jan 11 2010 Jens Petersen - 6.12.1-4 +- ghc-rpm-macros-0.5.4 fixes wrong version requires between lib subpackages + * Mon Jan 11 2010 Jens Petersen - 6.12.1-3 - ghc-rpm-macros-0.5.2 fixes broken pkg_name requires for lib subpackages From 205495df99e99590264e266c50059a33a31fc32f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 12:46:27 +0000 Subject: [PATCH 139/530] ghc-mtl package was added to fedora so filtering it again --- ghc-6.12.1-no-filter-libs.patch | 2 +- ghc.spec | 9 +++++---- 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/ghc-6.12.1-no-filter-libs.patch b/ghc-6.12.1-no-filter-libs.patch index 6e67baa..8860483 100644 --- a/ghc-6.12.1-no-filter-libs.patch +++ b/ghc-6.12.1-no-filter-libs.patch @@ -6,7 +6,7 @@ diff -u ghc-6.12.1/ghc.mk\~ ghc-6.12.1/ghc.mk endif -INSTALLED_PACKAGES = $(filter-out haskeline mtl terminfo,$(PACKAGES)) -+INSTALLED_PACKAGES = $(PACKAGES) ++INSTALLED_PACKAGES = $(filter-out mtl,$(PACKAGES)) HIDDEN_PACKAGES = ghc-binary define set_INSTALL_DISTDIR diff --git a/ghc.spec b/ghc.spec index 768ae4e..f16beef 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 # can't be reset as long as there are versioned subpackages -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -111,8 +111,6 @@ They should be installed when GHC's profiling subsystem is needed. %ghc_binlib_package -n haskeline -v 0.6.2.1 -%ghc_binlib_package -n mtl -v 1.1.0.2 - %ghc_binlib_package -n terminfo -v 0.3.1.1 %global version %{ghc_version_override} @@ -185,7 +183,7 @@ sed -i -e "/ghc-%{version}-.*.conf\$/d" ghc.files sed -i -e "/ghc-%{version}\$/d" ghc-doc.files %ghc_gen_filelists ghc -for pkg in haskeline-0.6.2.1 mtl-1.1.0.2 terminfo-0.3.1.1; do +for pkg in haskeline-0.6.2.1 terminfo-0.3.1.1; do sed -i -e "/ghc-%{version}\/$pkg/d" ghc.files ghc-libs.files sed -i -e "/$pkg-.*.conf\$/d" ghc.files sed -i -e "/$pkg\$/d" ghc-doc.files @@ -297,6 +295,9 @@ ghc-pkg recache %endif %changelog +* Mon Jan 11 2010 Jens Petersen - 6.12.1-5 +- ghc-mtl package was added to fedora so dropping it from here + * Mon Jan 11 2010 Jens Petersen - 6.12.1-4 - ghc-rpm-macros-0.5.4 fixes wrong version requires between lib subpackages From 7b2f6a749e4b73e4e7ab9a09d7c7cbd9b9fc91cb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 14:28:48 +0000 Subject: [PATCH 140/530] try dropping all haskeline, mtl, and terminfo to build --- ghc.spec | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/ghc.spec b/ghc.spec index f16beef..3f235ec 100644 --- a/ghc.spec +++ b/ghc.spec @@ -120,7 +120,7 @@ They should be installed when GHC's profiling subsystem is needed. # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig # install more libs -%patch2 -p1 -b .orig +#%%patch2 -p1 -b .orig # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -177,20 +177,20 @@ sed -i -e "s|\.%{_prefix}|%{_prefix}|" *.files cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files cat rpm-dev-dir.files rpm-base.files > ghc.files -# subpackage ghc and extra libraries +# subpackage ghc libraries sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files sed -i -e "/ghc-%{version}-.*.conf\$/d" ghc.files sed -i -e "/ghc-%{version}\$/d" ghc-doc.files %ghc_gen_filelists ghc -for pkg in haskeline-0.6.2.1 terminfo-0.3.1.1; do - sed -i -e "/ghc-%{version}\/$pkg/d" ghc.files ghc-libs.files - sed -i -e "/$pkg-.*.conf\$/d" ghc.files - sed -i -e "/$pkg\$/d" ghc-doc.files - name=$(echo $pkg | sed -e "s/\(.*\)-.*/\1/") - version=$(echo $pkg | sed -e "s/.*-\(.*\)/\1/") - %ghc_gen_filelists ${name} ${version} -done +#for pkg in haskeline-0.6.2.1 terminfo-0.3.1.1; do +# sed -i -e "/ghc-%{version}\/$pkg/d" ghc.files ghc-libs.files +# sed -i -e "/$pkg-.*.conf\$/d" ghc.files +# sed -i -e "/$pkg\$/d" ghc-doc.files +# name=$(echo $pkg | sed -e "s/\(.*\)-.*/\1/") +# version=$(echo $pkg | sed -e "s/.*-\(.*\)/\1/") +# %%ghc_gen_filelists ${name} ${version} +#done # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -296,7 +296,8 @@ ghc-pkg recache %changelog * Mon Jan 11 2010 Jens Petersen - 6.12.1-5 -- ghc-mtl package was added to fedora so dropping it from here +- drop extras packages again (haskeline, mtl, and terminfo) +- ghc-mtl package was added to fedora * Mon Jan 11 2010 Jens Petersen - 6.12.1-4 - ghc-rpm-macros-0.5.4 fixes wrong version requires between lib subpackages From 5f19e51ca3d06d80e8d07a7f8cdb274529d1b376 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 15:41:30 +0000 Subject: [PATCH 141/530] - drop ghc-6.12.1-no-filter-libs.patch - filter ghc lib files from ghc-prof --- ghc-6.12.1-no-filter-libs.patch | 12 ------------ ghc.spec | 17 +++-------------- 2 files changed, 3 insertions(+), 26 deletions(-) delete mode 100644 ghc-6.12.1-no-filter-libs.patch diff --git a/ghc-6.12.1-no-filter-libs.patch b/ghc-6.12.1-no-filter-libs.patch deleted file mode 100644 index 8860483..0000000 --- a/ghc-6.12.1-no-filter-libs.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc-6.12.1/ghc.mk\~ ghc-6.12.1/ghc.mk ---- ghc-6.12.1/ghc.mk~ 2009-12-11 04:11:33.000000000 +1000 -+++ ghc-6.12.1/ghc.mk 2010-01-09 23:17:20.000000000 +1000 -@@ -846,7 +846,7 @@ - INSTALLED_GHC_PKG_REAL=$(DESTDIR)$(bindir)/ghc-pkg.exe - endif - --INSTALLED_PACKAGES = $(filter-out haskeline mtl terminfo,$(PACKAGES)) -+INSTALLED_PACKAGES = $(filter-out mtl,$(PACKAGES)) - HIDDEN_PACKAGES = ghc-binary - - define set_INSTALL_DISTDIR diff --git a/ghc.spec b/ghc.spec index 3f235ec..3950a49 100644 --- a/ghc.spec +++ b/ghc.spec @@ -58,7 +58,6 @@ BuildRequires: libxslt, docbook-style-xsl BuildRequires: hscolour %endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch -Patch2: ghc-6.12.1-no-filter-libs.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -119,8 +118,6 @@ They should be installed when GHC's profiling subsystem is needed. %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig -# install more libs -#%%patch2 -p1 -b .orig # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -178,20 +175,11 @@ cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files cat rpm-dev-dir.files rpm-base.files > ghc.files # subpackage ghc libraries -sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files +sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files ghc-prof.files sed -i -e "/ghc-%{version}-.*.conf\$/d" ghc.files sed -i -e "/ghc-%{version}\$/d" ghc-doc.files %ghc_gen_filelists ghc -#for pkg in haskeline-0.6.2.1 terminfo-0.3.1.1; do -# sed -i -e "/ghc-%{version}\/$pkg/d" ghc.files ghc-libs.files -# sed -i -e "/$pkg-.*.conf\$/d" ghc.files -# sed -i -e "/$pkg\$/d" ghc-doc.files -# name=$(echo $pkg | sed -e "s/\(.*\)-.*/\1/") -# version=$(echo $pkg | sed -e "s/.*-\(.*\)/\1/") -# %%ghc_gen_filelists ${name} ${version} -#done - # these are handled as alternatives for i in hsc2hs runhaskell; do if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then @@ -296,7 +284,8 @@ ghc-pkg recache %changelog * Mon Jan 11 2010 Jens Petersen - 6.12.1-5 -- drop extras packages again (haskeline, mtl, and terminfo) +- drop ghc-6.12.1-no-filter-libs.patch and extras packages again +- filter ghc-ghc-prof files from ghc-prof - ghc-mtl package was added to fedora * Mon Jan 11 2010 Jens Petersen - 6.12.1-4 From 89aaac8f3555463455f7402ab3de502b082b300d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 22:55:52 +0000 Subject: [PATCH 142/530] remove the ghc_binlib_package for haskeline and terminfo too! --- ghc.spec | 4 ---- 1 file changed, 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3950a49..65823ca 100644 --- a/ghc.spec +++ b/ghc.spec @@ -108,10 +108,6 @@ They should be installed when GHC's profiling subsystem is needed. %ghc_binlib_package -n ghc -%ghc_binlib_package -n haskeline -v 0.6.2.1 - -%ghc_binlib_package -n terminfo -v 0.3.1.1 - %global version %{ghc_version_override} %prep From a6e9993668f77703442cdd080f154d1dc92c0c91 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 11 Jan 2010 23:16:08 +0000 Subject: [PATCH 143/530] clean away release reset comment and version reset too --- ghc.spec | 3 --- 1 file changed, 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 65823ca..cdec772 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,6 @@ Name: ghc # break of haskell-platform-2009.2.0.2 Version: 6.12.1 -# can't be reset as long as there are versioned subpackages Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: @@ -108,8 +107,6 @@ They should be installed when GHC's profiling subsystem is needed. %ghc_binlib_package -n ghc -%global version %{ghc_version_override} - %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} # absolute haddock path (was for html/libraries -> libraries) From be9079ab142bc69eda54d2f85074bcf50bcfd3f2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 23 Apr 2010 04:09:50 +0000 Subject: [PATCH 144/530] - update to 6.12.2 - add testsuite with bcond and run it in check section --- .cvsignore | 3 ++- ghc.spec | 19 +++++++++++++++---- sources | 3 ++- 3 files changed, 19 insertions(+), 6 deletions(-) diff --git a/.cvsignore b/.cvsignore index 7ef14bc..1be4562 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1 +1,2 @@ -ghc-6.12.1-src.tar.bz2 +ghc-6.12.2-src.tar.bz2 +testsuite-6.12.2.tar.bz2 diff --git a/ghc.spec b/ghc.spec index cdec772..0b87a8c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,6 +9,8 @@ %bcond_without prof # build xml manuals (users_guide, etc) %bcond_without manual +# run testsuite +%bcond_without testsuite ## default disabled options ## # include extralibs @@ -24,9 +26,9 @@ %global debug_package %{nil} Name: ghc -# break of haskell-platform-2009.2.0.2 -Version: 6.12.1 -Release: 5%{?dist} +# break of haskell-platform-2010.1.0.0 +Version: 6.12.2 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -36,6 +38,7 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{with extralibs} Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 %endif +Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) Obsoletes: ghc682, ghc681, haddock09 @@ -108,7 +111,7 @@ They should be installed when GHC's profiling subsystem is needed. %ghc_binlib_package -n ghc %prep -%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} +%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} -b2 # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig @@ -201,6 +204,10 @@ inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* %endif +%if %{with testsuite} +cd testsuite +make +%endif %clean rm -rf $RPM_BUILD_ROOT @@ -276,6 +283,10 @@ ghc-pkg recache %endif %changelog +* Fri Apr 23 2010 Jens Petersen - 6.12.2-1 +- update to 6.12.2 +- add testsuite with bcond and run it in check section + * Mon Jan 11 2010 Jens Petersen - 6.12.1-5 - drop ghc-6.12.1-no-filter-libs.patch and extras packages again - filter ghc-ghc-prof files from ghc-prof diff --git a/sources b/sources index 613cc7b..78754ff 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ -3a2b23f29013605f721ebdfc29de9c92 ghc-6.12.1-src.tar.bz2 +8997fb240183fa0af61a4a971741b392 ghc-6.12.2-src.tar.bz2 +07e7bdf0f0742889cebf47e5b977bf6c testsuite-6.12.2.tar.bz2 From 4d4ecfaac7ca8fcecd77eaec46111a1d57577015 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 23 Apr 2010 04:41:21 +0000 Subject: [PATCH 145/530] uploaded complete tarball --- sources | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sources b/sources index 78754ff..15fa29c 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -8997fb240183fa0af61a4a971741b392 ghc-6.12.2-src.tar.bz2 +b7ab3d3c2d58534cb3f31a00e2c12c67 ghc-6.12.2-src.tar.bz2 07e7bdf0f0742889cebf47e5b977bf6c testsuite-6.12.2.tar.bz2 From 16ee9ca997470600783184eabb2b1669f361a066 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 23 Apr 2010 06:01:01 +0000 Subject: [PATCH 146/530] - BR python for testsuite - note break of haskell-platform-2010.1.0.0 - forward port following fixes from F-13 branch: - drop old ghc682, ghc681, haddock09 obsoletes - drop haddock_version and no longer provide haddock explicitly - add obsoletes for ghc-utf8-string (#571478, reported by Jochen Schmitt) - update ghc-rpm-macros BR to 0.5.6 for ghc_pkg_recache --- ghc.spec | 40 ++++++++++++++++++++++++++-------------- 1 file changed, 26 insertions(+), 14 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0b87a8c..0d3378c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,8 +20,6 @@ # include colored html src %bcond_with hscolour -%global haddock_version 2.5.0 - # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} @@ -41,11 +39,11 @@ Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) -Obsoletes: ghc682, ghc681, haddock09 -# introduced for f11 and can be removed for f13: -Obsoletes: haddock < %{haddock_version}, ghc-haddock-devel < %{haddock_version} -Provides: haddock = %{haddock_version} -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.2 +# introduced for f11 +Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 +# added for f13 +Obsoletes: ghc-utf8-string-devel < 0.3.6-3 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.6 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -59,6 +57,9 @@ BuildRequires: libxslt, docbook-style-xsl %if %{with hscolour} BuildRequires: hscolour %endif +%if %{with testsuite} +BuildRequires: python +%endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch %description @@ -77,7 +78,9 @@ Group: Development/Languages Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} -Obsoletes: ghc-haddock-doc < %{haddock_version} +Obsoletes: ghc-haddock-doc < 2.4.2-3 +# added for f13 +Obsoletes: ghc-utf8-string-doc < 0.3.6-3 %description doc Preformatted documentation for the Glorious Glasgow Haskell Compilation System @@ -88,6 +91,8 @@ access to the documentation in HTML format. %package libs Summary: Shared libraries for GHC Group: Development/Libraries +# added for f13 +Obsoletes: ghc-utf8-string < 0.3.6-3 %description libs Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -98,8 +103,9 @@ Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). Summary: Profiling libraries for GHC Group: Development/Libraries Requires: %{name} = %{version}-%{release} -Obsoletes: ghc682-prof, ghc681-prof -Obsoletes: ghc-haddock-prof < %{haddock_version} +Obsoletes: ghc-haddock-prof < 2.4.2-3 +# added for f13 +Obsoletes: ghc-utf8-string-prof < 0.3.6-3 %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -205,8 +211,7 @@ inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic rm testghc/* %endif %if %{with testsuite} -cd testsuite -make +make -C testsuite %endif %clean @@ -238,7 +243,7 @@ fi %posttrans # (posttrans to make sure any old libs have been removed first) -ghc-pkg recache +%ghc_pkg_recache %posttrans doc # (posttrans to make sure any old docs have been removed first) @@ -285,7 +290,14 @@ ghc-pkg recache %changelog * Fri Apr 23 2010 Jens Petersen - 6.12.2-1 - update to 6.12.2 -- add testsuite with bcond and run it in check section +- add testsuite with bcond, run it in check section, and BR python + +* Mon Apr 12 2010 Jens Petersen - 6.12.1-6 +- ghc-6.12.1 is part of haskell-platform-2010.1.0.0 +- drop old ghc682, ghc681, haddock09 obsoletes +- drop haddock_version and no longer provide haddock explicitly +- add obsoletes for ghc-utf8-string (#571478, reported by Jochen Schmitt) +- update ghc-rpm-macros BR to 0.5.6 for ghc_pkg_recache * Mon Jan 11 2010 Jens Petersen - 6.12.1-5 - drop ghc-6.12.1-no-filter-libs.patch and extras packages again From c698ee76c3d555ccee04d7e3885425a7077888e2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 May 2010 04:13:45 +0000 Subject: [PATCH 147/530] script to generate dependency graph of fedora haskell packages --- pkg-deps.sh | 18 ++++++++++++++++++ 1 file changed, 18 insertions(+) create mode 100755 pkg-deps.sh diff --git a/pkg-deps.sh b/pkg-deps.sh new file mode 100755 index 0000000..b181215 --- /dev/null +++ b/pkg-deps.sh @@ -0,0 +1,18 @@ +#!/bin/sh + +set -e + +mkdir -p .pkg-deps + +cd .pkg-deps + +ghc-pkg dot --global > pkgs.dot + +cp -p pkgs.dot pkgs.dot.orig + +GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random syb template-haskell time unix Win32" + +# ignore library packages provided by ghc +for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done + +cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg From 17699b895c65f0de872fed1bea97f1677ee2c35a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 May 2010 10:02:47 +0000 Subject: [PATCH 148/530] - add utf8-string-0.3.4 - run xdg-open on svg file - short description --- pkg-deps.sh | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index b181215..4a7d753 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -1,5 +1,8 @@ #!/bin/sh +# script to generate dependency graph for fedora haskell libraries +# requires ghc, ghc-*-devel and graphviz to be installed + set -e mkdir -p .pkg-deps @@ -10,9 +13,11 @@ ghc-pkg dot --global > pkgs.dot cp -p pkgs.dot pkgs.dot.orig -GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random syb template-haskell time unix Win32" +GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random syb template-haskell time unix utf8-string-0.3.4 Win32" # ignore library packages provided by ghc for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg + +xdg-open pkgs.svg From d06a8f2815a205cf48931bd7eab17c7417e68d4c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 May 2010 10:20:06 +0000 Subject: [PATCH 149/530] - drop ghc-utf8-string obsoletes since it is no longer provided - run testsuite fast --- ghc.spec | 15 +++++---------- 1 file changed, 5 insertions(+), 10 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0d3378c..ca38e90 100644 --- a/ghc.spec +++ b/ghc.spec @@ -41,8 +41,6 @@ URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 -# added for f13 -Obsoletes: ghc-utf8-string-devel < 0.3.6-3 BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.6 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel @@ -79,8 +77,6 @@ Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} Obsoletes: ghc-haddock-doc < 2.4.2-3 -# added for f13 -Obsoletes: ghc-utf8-string-doc < 0.3.6-3 %description doc Preformatted documentation for the Glorious Glasgow Haskell Compilation System @@ -91,8 +87,6 @@ access to the documentation in HTML format. %package libs Summary: Shared libraries for GHC Group: Development/Libraries -# added for f13 -Obsoletes: ghc-utf8-string < 0.3.6-3 %description libs Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -104,8 +98,6 @@ Summary: Profiling libraries for GHC Group: Development/Libraries Requires: %{name} = %{version}-%{release} Obsoletes: ghc-haddock-prof < 2.4.2-3 -# added for f13 -Obsoletes: ghc-utf8-string-prof < 0.3.6-3 %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -211,7 +203,7 @@ inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic rm testghc/* %endif %if %{with testsuite} -make -C testsuite +make -C testsuite/tests/ghc-regress fast %endif %clean @@ -288,6 +280,10 @@ fi %endif %changelog +* Tue May 25 2010 Jens Petersen +- drop ghc-utf8-string obsoletes since it is no longer provided +- run testsuite fast + * Fri Apr 23 2010 Jens Petersen - 6.12.2-1 - update to 6.12.2 - add testsuite with bcond, run it in check section, and BR python @@ -296,7 +292,6 @@ fi - ghc-6.12.1 is part of haskell-platform-2010.1.0.0 - drop old ghc682, ghc681, haddock09 obsoletes - drop haddock_version and no longer provide haddock explicitly -- add obsoletes for ghc-utf8-string (#571478, reported by Jochen Schmitt) - update ghc-rpm-macros BR to 0.5.6 for ghc_pkg_recache * Mon Jan 11 2010 Jens Petersen - 6.12.1-5 From 9d4f5cb6137e6336f603d16db43ef7b52983ce89 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 28 May 2010 06:40:59 +0000 Subject: [PATCH 150/530] - (6.12.3 rc1) - ghost package.cache - fix description and summary of ghc internal library (John Obbele) --- ghc.spec | 17 ++++++++++++----- 1 file changed, 12 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index ca38e90..8525500 100644 --- a/ghc.spec +++ b/ghc.spec @@ -25,7 +25,7 @@ Name: ghc # break of haskell-platform-2010.1.0.0 -Version: 6.12.2 +Version: 6.12.2.20100521 Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: @@ -36,7 +36,9 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{with extralibs} Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 %endif +%if %{with testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 +%endif URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 @@ -106,10 +108,12 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc +%ghc_binlib_package -n ghc -s "GHC internals library" -d \ +"The API for GHC internals can be used for example to analyse, transform, and\ +dynamically load Haskell code." %prep -%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} -b2 +%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig @@ -246,7 +250,7 @@ fi %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* %dir %{_libdir}/%{name}-%{version} -%config(noreplace) %{_libdir}/%{name}-%{version}/package.conf.d/package.cache +%ghost %{_libdir}/%{name}-%{version}/package.conf.d/package.cache %if %{with manual} %{_mandir}/man1/ghc.* %endif @@ -280,9 +284,12 @@ fi %endif %changelog -* Tue May 25 2010 Jens Petersen +* Fri May 28 2010 Jens Petersen - 6.12.2.20100521-1 +- 6.12.3 rc1 +- ghost package.cache - drop ghc-utf8-string obsoletes since it is no longer provided - run testsuite fast +- fix description and summary of ghc internal library (John Obbele) * Fri Apr 23 2010 Jens Petersen - 6.12.2-1 - update to 6.12.2 From 495747b71088a4f72cc0f5082df8584099080de6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 Jun 2010 08:31:03 +0000 Subject: [PATCH 151/530] - add hack to include bin packages too - ignore rts and ffi from ghc too --- pkg-deps.sh | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 4a7d753..bbfe3ac 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -9,13 +9,22 @@ mkdir -p .pkg-deps cd .pkg-deps -ghc-pkg dot --global > pkgs.dot +# remove the closing line +ghc-pkg dot --global | sed '$d' > pkgs.dot -cp -p pkgs.dot pkgs.dot.orig +# check for binary deps too +for i in alex cabal-install cpphs darcs happy hedgewars hscolour kaya xmonad; do + PKG=`rpm -q --qf "%{name}-%{version}" $i` || echo $i is not installed + rpm -q --requires $i | grep ghc6 | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc6.*/\"/" >> pkgs.dot +done + +# and add it back +echo "}" >> pkgs.dot -GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random syb template-haskell time unix utf8-string-0.3.4 Win32" +cp -p pkgs.dot pkgs.dot.orig # ignore library packages provided by ghc +GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix utf8-string-0.3.4 Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg From 5e9ae7fc32575490ac8e2940c8ab424ebc037999 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 3 Jun 2010 04:59:32 +0000 Subject: [PATCH 152/530] also include haskell-platform binary package --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index bbfe3ac..aa2ba04 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,7 +13,7 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too -for i in alex cabal-install cpphs darcs happy hedgewars hscolour kaya xmonad; do +for i in alex cabal-install cpphs darcs happy haskell-platform hedgewars hscolour kaya xmonad; do PKG=`rpm -q --qf "%{name}-%{version}" $i` || echo $i is not installed rpm -q --requires $i | grep ghc6 | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc6.*/\"/" >> pkgs.dot done From c3e8b642b9ac8ac49a25f863bf424fa019e41ec9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 3 Jun 2010 07:22:29 +0000 Subject: [PATCH 153/530] only run xdg-open if there is DISPLAY --- pkg-deps.sh | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index aa2ba04..e581bf4 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -29,4 +29,6 @@ for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg -xdg-open pkgs.svg +if [ -n "$DISPLAY"]; then + xdg-open pkgs.svg +fi From 0cb619abe62111f4ba68d739491f47db2325fe0c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 3 Jun 2010 07:25:14 +0000 Subject: [PATCH 154/530] fix test for display --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index e581bf4..9309b2c 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -29,6 +29,6 @@ for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg -if [ -n "$DISPLAY"]; then +if [ -n "$DISPLAY" ]; then xdg-open pkgs.svg fi From 63986ca7f53225e9f9c2fca60ed62a6c4ebfd317 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 3 Jun 2010 12:38:38 +0000 Subject: [PATCH 155/530] - drop binlib packages from bin rpm hack - special-case haskell-platform bin - bring back utf8-string - include ghc lib since we subpackage it --- pkg-deps.sh | 24 +++++++++++++++++------- 1 file changed, 17 insertions(+), 7 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 9309b2c..da0ecdc 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -3,7 +3,7 @@ # script to generate dependency graph for fedora haskell libraries # requires ghc, ghc-*-devel and graphviz to be installed -set -e +set -e +x mkdir -p .pkg-deps @@ -12,10 +12,20 @@ cd .pkg-deps # remove the closing line ghc-pkg dot --global | sed '$d' > pkgs.dot -# check for binary deps too -for i in alex cabal-install cpphs darcs happy haskell-platform hedgewars hscolour kaya xmonad; do - PKG=`rpm -q --qf "%{name}-%{version}" $i` || echo $i is not installed - rpm -q --requires $i | grep ghc6 | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc6.*/\"/" >> pkgs.dot +# check for binary deps too (but not binlib) +for i in alex cabal-install happy haskell-platform hedgewars kaya; do + PKG_THERE=yes + PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no + if [ "$PKG_THERE" = "yes" ]; then + case $i in + haskell-platform) + rpm -q --requires $i | grep -v rpmlib | grep -v ghc | sed -e "s/^/\"$PKG\" -> \"/g" -e "s/ = \(.*\)/-\1\"/" >> pkgs.dot + ;; + *) + rpm -q --requires $i | grep ghc6 | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc6.*/\"/" >> pkgs.dot + ;; + esac + fi done # and add it back @@ -23,8 +33,8 @@ echo "}" >> pkgs.dot cp -p pkgs.dot pkgs.dot.orig -# ignore library packages provided by ghc -GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-6.12 ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix utf8-string-0.3.4 Win32" +# ignore library packages provided by ghc (except ghc-6.12) +GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg From b6bfcab66dbca0553f7a212cf880a314e98c4e0a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 20 Jun 2010 13:01:02 +0000 Subject: [PATCH 156/530] - 6.12.3 release - build with hscolour - use ghc-rpm-macro-0.5.8 for ghc_strip_shared macro --- .cvsignore | 4 ++-- ghc.spec | 16 ++++++++++++---- sources | 4 ++-- 3 files changed, 16 insertions(+), 8 deletions(-) diff --git a/.cvsignore b/.cvsignore index 1be4562..4a3c164 100644 --- a/.cvsignore +++ b/.cvsignore @@ -1,2 +1,2 @@ -ghc-6.12.2-src.tar.bz2 -testsuite-6.12.2.tar.bz2 +ghc-6.12.3-src.tar.bz2 +testsuite-6.12.3.tar.bz2 diff --git a/ghc.spec b/ghc.spec index 8525500..72ae699 100644 --- a/ghc.spec +++ b/ghc.spec @@ -11,21 +11,21 @@ %bcond_without manual # run testsuite %bcond_without testsuite +# include colored html src +%bcond_without hscolour ## default disabled options ## # include extralibs %bcond_with extralibs # quick build profile %bcond_with quick -# include colored html src -%bcond_with hscolour # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} Name: ghc # break of haskell-platform-2010.1.0.0 -Version: 6.12.2.20100521 +Version: 6.12.3 Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: @@ -43,7 +43,7 @@ URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.6 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.8 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -187,6 +187,9 @@ for i in hsc2hs runhaskell; do fi done +%ghc_strip_shared + + %check # stolen from ghc6/debian/rules: # Do some very simple tests that the compiler actually works @@ -284,6 +287,11 @@ fi %endif %changelog +* Mon Jun 14 2010 Jens Petersen - 6.12.3-1 +- 6.12.3 +- build with hscolour +- use ghc-rpm-macro-0.5.8 for ghc_strip_shared macro + * Fri May 28 2010 Jens Petersen - 6.12.2.20100521-1 - 6.12.3 rc1 - ghost package.cache diff --git a/sources b/sources index 15fa29c..e7c5106 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -b7ab3d3c2d58534cb3f31a00e2c12c67 ghc-6.12.2-src.tar.bz2 -07e7bdf0f0742889cebf47e5b977bf6c testsuite-6.12.2.tar.bz2 +4c2663c2eff833d7b9f39ef770eefbd6 ghc-6.12.3-src.tar.bz2 +5c6143040d043f10e6d014cd5fd8ca36 testsuite-6.12.3.tar.bz2 From 2c2e6bed6ca9a6ca50610a3fa0596d8b7d5cb6f9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 20 Jun 2010 23:13:58 +0000 Subject: [PATCH 157/530] fix description of ghc-ghc --- ghc.spec | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 72ae699..ed3e6e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -108,9 +108,7 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc -s "GHC internals library" -d \ -"The API for GHC internals can be used for example to analyse, transform, and\ -dynamically load Haskell code." +%ghc_binlib_package -n ghc -s "GHC internals library" -d "The API for GHC internals can be used for example to analyse, transform, and\ndynamically load Haskell code." -o 6.12.3-1 %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} From d3940a51d02d8d8995c73ced316a6a88702282b6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 20 Jun 2010 23:19:09 +0000 Subject: [PATCH 158/530] remove erroneous -o pkg merge option to ghc-ghc --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index ed3e6e2..e59d810 100644 --- a/ghc.spec +++ b/ghc.spec @@ -108,7 +108,7 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc -s "GHC internals library" -d "The API for GHC internals can be used for example to analyse, transform, and\ndynamically load Haskell code." -o 6.12.3-1 +%ghc_binlib_package -n ghc -s "GHC internals library" -d "The API for GHC internals can be used for example to analyse, transform, and\ndynamically load Haskell code." %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} From aee0ea8fc1c123d219b7528ff5a111155f4b3dda Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 23 Jun 2010 10:30:14 +0000 Subject: [PATCH 159/530] strip all dynlinked files not just shared objects (ghc-rpm-macros-0.5.9) --- ghc.spec | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index e59d810..15a32b4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # break of haskell-platform-2010.1.0.0 Version: 6.12.3 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -43,7 +43,7 @@ URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.8 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.9 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -185,7 +185,7 @@ for i in hsc2hs runhaskell; do fi done -%ghc_strip_shared +%ghc_strip_dynlinked %check @@ -285,6 +285,9 @@ fi %endif %changelog +* Wed Jun 23 2010 Jens Petersen - 6.12.3-2 +- strip all dynlinked files not just shared objects (ghc-rpm-macros-0.5.9) + * Mon Jun 14 2010 Jens Petersen - 6.12.3-1 - 6.12.3 - build with hscolour From dc71f25047d20eacd3ad2f0158832cfe77512944 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 24 Jun 2010 03:16:12 +0000 Subject: [PATCH 160/530] - drop the broken summary and description args to the ghc-ghc package and use ghc-rpm-macros-0.6.1 --- ghc.spec | 13 +++++++++---- 1 file changed, 9 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 15a32b4..dcecd36 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # break of haskell-platform-2010.1.0.0 Version: 6.12.3 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -43,7 +43,7 @@ URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.5.9 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.6.1 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -108,7 +108,7 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc -s "GHC internals library" -d "The API for GHC internals can be used for example to analyse, transform, and\ndynamically load Haskell code." +%ghc_binlib_package -n ghc %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} @@ -285,11 +285,16 @@ fi %endif %changelog +* Thu Jun 24 2010 Jens Petersen - 6.12.3-3 +- drop the broken summary and description args to the ghc-ghc package + and use ghc-rpm-macros-0.6.1 + * Wed Jun 23 2010 Jens Petersen - 6.12.3-2 - strip all dynlinked files not just shared objects (ghc-rpm-macros-0.5.9) * Mon Jun 14 2010 Jens Petersen - 6.12.3-1 -- 6.12.3 +- 6.12.3 release: + http://darcs.haskell.org/download/docs/6.12.3/html/users_guide/release-6-12-3.html - build with hscolour - use ghc-rpm-macro-0.5.8 for ghc_strip_shared macro From a362bcafa0fac919cf4547cdc1da033ec80db453 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 24 Jun 2010 23:52:16 +0000 Subject: [PATCH 161/530] add hlint to pkg-deps.sh --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index da0ecdc..4ad2c8b 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,7 +13,7 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too (but not binlib) -for i in alex cabal-install happy haskell-platform hedgewars kaya; do +for i in alex cabal-install happy haskell-platform hedgewars hlint kaya; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no if [ "$PKG_THERE" = "yes" ]; then From e328bbd33ca6a66dea073c373ba2620a23423582 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 28 Jun 2010 05:52:48 +0000 Subject: [PATCH 162/530] more hacks to add singleton packages --- pkg-deps.sh | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 4ad2c8b..4d0aa3d 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -12,11 +12,12 @@ cd .pkg-deps # remove the closing line ghc-pkg dot --global | sed '$d' > pkgs.dot -# check for binary deps too (but not binlib) -for i in alex cabal-install happy haskell-platform hedgewars hlint kaya; do +# check for binary deps too +for i in alex cabal-install cpphs darcs ghc happy haskell-platform hedgewars hscolour kaya xmonad; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no if [ "$PKG_THERE" = "yes" ]; then + echo \"$PKG\" >> pkgs.dot case $i in haskell-platform) rpm -q --requires $i | grep -v rpmlib | grep -v ghc | sed -e "s/^/\"$PKG\" -> \"/g" -e "s/ = \(.*\)/-\1\"/" >> pkgs.dot @@ -28,6 +29,9 @@ for i in alex cabal-install happy haskell-platform hedgewars hlint kaya; do fi done +# make sure all libs there +rpm -qa --qf "\"%{name}-%{version}\"\n" ghc-\* | egrep -v -- "(ghc-libs|-prof|-devel|-doc)-" | sed -e s/^\"ghc-/\"/g >> pkgs.dot + # and add it back echo "}" >> pkgs.dot @@ -41,4 +45,6 @@ cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg if [ -n "$DISPLAY" ]; then xdg-open pkgs.svg +else + echo open ".pkg-deps/pkgs.svg" to display pkg graph fi From 24005bb6f4b5c3660cf2ee13b1e9606c1702115a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2010 09:16:11 +0000 Subject: [PATCH 163/530] obsolete ghc-time to smooth f13 upgrades --- ghc.spec | 10 +++++++++- 1 file changed, 9 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index dcecd36..1326c45 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # break of haskell-platform-2010.1.0.0 Version: 6.12.3 -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -43,6 +43,8 @@ URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 +# introduced for f14 +Obsoletes: ghc-time-devel < 1.1.2.4-5 BuildRequires: ghc, happy, ghc-rpm-macros >= 0.6.1 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel @@ -79,6 +81,7 @@ Requires: %{name} = %{version}-%{release} # for haddock Requires(posttrans): %{name} = %{version}-%{release} Obsoletes: ghc-haddock-doc < 2.4.2-3 +Obsoletes: ghc-time-doc < 1.1.2.4-5 %description doc Preformatted documentation for the Glorious Glasgow Haskell Compilation System @@ -89,6 +92,7 @@ access to the documentation in HTML format. %package libs Summary: Shared libraries for GHC Group: Development/Libraries +Obsoletes: ghc-time < 1.1.2.4-5 %description libs Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -100,6 +104,7 @@ Summary: Profiling libraries for GHC Group: Development/Libraries Requires: %{name} = %{version}-%{release} Obsoletes: ghc-haddock-prof < 2.4.2-3 +Obsoletes: ghc-time-prof < 1.1.2.4-5 %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -285,6 +290,9 @@ fi %endif %changelog +* Thu Jul 15 2010 Jens Petersen - 6.12.3-4 +- obsolete ghc-time + * Thu Jun 24 2010 Jens Petersen - 6.12.3-3 - drop the broken summary and description args to the ghc-ghc package and use ghc-rpm-macros-0.6.1 From 9956691973cbf607e9b961e4c17b8bd7d6e2adeb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2010 13:48:00 +0000 Subject: [PATCH 164/530] - merge ghc-doc into base package - note that ghc-6.12.3 is part of haskell-platform-2010.2.0.0 --- ghc.spec | 44 +++++++++++++++++--------------------------- 1 file changed, 17 insertions(+), 27 deletions(-) diff --git a/ghc.spec b/ghc.spec index 1326c45..5ca1ed5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -24,7 +24,7 @@ %global debug_package %{nil} Name: ghc -# break of haskell-platform-2010.1.0.0 +# part of haskell-platform-2010.2.0.0 Version: 6.12.3 Release: 4%{?dist} Summary: Glasgow Haskell Compilation system @@ -41,10 +41,15 @@ Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 %endif URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) +# introduced for f14 +Obsoletes: ghc-doc < 6.12.3-4 +Provides: ghc-doc = %{version}-%{release} # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 +Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f14 Obsoletes: ghc-time-devel < 1.1.2.4-5 +Obsoletes: ghc-time-doc < 1.1.2.4-5 BuildRequires: ghc, happy, ghc-rpm-macros >= 0.6.1 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel @@ -74,20 +79,6 @@ collection of libraries, and support for various language extensions, including concurrency, exceptions, and a foreign language interface. -%package doc -Summary: Documentation for GHC -Group: Development/Languages -Requires: %{name} = %{version}-%{release} -# for haddock -Requires(posttrans): %{name} = %{version}-%{release} -Obsoletes: ghc-haddock-doc < 2.4.2-3 -Obsoletes: ghc-time-doc < 1.1.2.4-5 - -%description doc -Preformatted documentation for the Glorious Glasgow Haskell Compilation System -(GHC) and its libraries. It should be installed if you like to have local -access to the documentation in HTML format. - %if %{with shared} %package libs Summary: Shared libraries for GHC @@ -161,24 +152,27 @@ rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install SRC_TOP=$PWD -#rm -f rpm-*.files ( cd $RPM_BUILD_ROOT + # library directories find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" + # library devel subdirs find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) + # split dyn, devel, conf and prof files find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) - find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/ghc-doc.files + # manuals (src dir are subdirs so dont duplicate them) + find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files ) # make paths absolute (filter "./usr" to "/usr") sed -i -e "s|\.%{_prefix}|%{_prefix}|" *.files cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files -cat rpm-dev-dir.files rpm-base.files > ghc.files +cat rpm-dev-dir.files rpm-base.files rpm-doc-dir.files > ghc.files # subpackage ghc libraries sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files ghc-prof.files -sed -i -e "/ghc-%{version}-.*.conf\$/d" ghc.files -sed -i -e "/ghc-%{version}\$/d" ghc-doc.files +sed -i -e "/ghc-%{version}\/package.conf.d\/ghc-%{version}-.*.conf\$/d" ghc.files +sed -i -e "/html\/libraries\/ghc-%{version}\$/d" ghc.files %ghc_gen_filelists ghc # these are handled as alternatives @@ -244,11 +238,8 @@ if [ "$1" = 0 ]; then fi %posttrans -# (posttrans to make sure any old libs have been removed first) +# (posttrans to make sure any old libs and docs have been removed first) %ghc_pkg_recache - -%posttrans doc -# (posttrans to make sure any old docs have been removed first) %ghc_reindex_haddock %files -f ghc.files @@ -260,9 +251,6 @@ fi %if %{with manual} %{_mandir}/man1/ghc.* %endif - -%files doc -f ghc-doc.files -%defattr(-,root,root,-) %if %{with doc} %dir %{ghcdocbasedir}/libraries %{ghcdocbasedir}/libraries/frames.html @@ -291,7 +279,9 @@ fi %changelog * Thu Jul 15 2010 Jens Petersen - 6.12.3-4 +- merge ghc-doc into base package - obsolete ghc-time +- note that ghc-6.12.3 is part of haskell-platform-2010.2.0.0 * Thu Jun 24 2010 Jens Petersen - 6.12.3-3 - drop the broken summary and description args to the ghc-ghc package From 355e48379dfadb5021698908fcc86898e9d3eadd Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2010 15:35:32 +0000 Subject: [PATCH 165/530] obsolete ghc-ghc-doc (ghc-rpm-macros-0.8.0) --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5ca1ed5..5c9943b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -50,7 +50,7 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f14 Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.6.1 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.8.0 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -104,7 +104,7 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc +%ghc_binlib_package -n ghc -o 6.12.3-4 %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} @@ -280,7 +280,7 @@ fi %changelog * Thu Jul 15 2010 Jens Petersen - 6.12.3-4 - merge ghc-doc into base package -- obsolete ghc-time +- obsolete ghc-time and ghc-ghc-doc (ghc-rpm-macros-0.8.0) - note that ghc-6.12.3 is part of haskell-platform-2010.2.0.0 * Thu Jun 24 2010 Jens Petersen - 6.12.3-3 From b39bdb20c7cc2fa98baa710119f402a0a67e8837 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 20 Jul 2010 09:07:52 +0000 Subject: [PATCH 166/530] add gtk2hs-buildtools to pkg-deps.sh --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 4d0aa3d..f20e0ae 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,7 +13,7 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too -for i in alex cabal-install cpphs darcs ghc happy haskell-platform hedgewars hscolour kaya xmonad; do +for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hedgewars hscolour kaya xmonad; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no if [ "$PKG_THERE" = "yes" ]; then From 354b3e302ae0dbdf83a5bacd16946275ba257a17 Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Wed, 28 Jul 2010 15:33:45 +0000 Subject: [PATCH 167/530] dist-git conversion --- .cvsignore => .gitignore | 0 Makefile | 21 --------------------- 2 files changed, 21 deletions(-) rename .cvsignore => .gitignore (100%) delete mode 100644 Makefile diff --git a/.cvsignore b/.gitignore similarity index 100% rename from .cvsignore rename to .gitignore diff --git a/Makefile b/Makefile deleted file mode 100644 index 8c346a3..0000000 --- a/Makefile +++ /dev/null @@ -1,21 +0,0 @@ -# Makefile for source rpm: ghc -# $Id$ -NAME := ghc -SPECFILE = $(NAME).spec - -define find-makefile-common -for d in common ../common ../../common ; do if [ -f $$d/Makefile.common ] ; then if [ -f $$d/CVS/Root -a -w $$d/Makefile.common ] ; then cd $$d ; cvs -Q update ; fi ; echo "$$d/Makefile.common" ; break ; fi ; done -endef - -MAKEFILE_COMMON := $(shell $(find-makefile-common)) - -ifeq ($(MAKEFILE_COMMON),) -# attept a checkout -define checkout-makefile-common -test -f CVS/Root && { cvs -Q -d $$(cat CVS/Root) checkout common && echo "common/Makefile.common" ; } || { echo "ERROR: I can't figure out how to checkout the 'common' module." ; exit -1 ; } >&2 -endef - -MAKEFILE_COMMON := $(shell $(checkout-makefile-common)) -endif - -include $(MAKEFILE_COMMON) From 78073395b5a3e670744ee8f858d22fcbc1e5e8f8 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 30 Jul 2010 12:15:23 +1000 Subject: [PATCH 168/530] obsolete old gtk2hs packages for smooth upgrades --- ghc.spec | 31 ++++++++++++++++++++++++++++++- 1 file changed, 30 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5c9943b..b6d3d5c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # part of haskell-platform-2010.2.0.0 Version: 6.12.3 -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -50,6 +50,19 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f14 Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 +# until new cabalized gtk2hs packages in f14+ +Obsoletes: ghc-cairo-devel < 0.11-1, ghc-cairo-doc < 0.11-1 +Obsoletes: ghc-gconf-devel < 0.11-1, ghc-gconf-doc < 0.11-1 +Obsoletes: ghc-gio-devel < 0.11-1, ghc-gio-doc < 0.11-1 +Obsoletes: ghc-glade-devel < 0.11-1, ghc-glade-doc < 0.11-1 +Obsoletes: ghc-glib-devel < 0.11-1, ghc-glib-doc < 0.11-1 +Obsoletes: ghc-gstreamer-devel < 0.11-1, ghc-gstreamer-doc < 0.11-1 +Obsoletes: ghc-gtk-devel < 0.11-1, ghc-gtk-doc < 0.11-1 +Obsoletes: ghc-gtkglext-devel < 0.11-1, ghc-gtkglext-doc < 0.11-1 +Obsoletes: ghc-gtksourceview2-devel < 0.11-1, ghc-gtksourceview2-doc < 0.11-1 +Obsoletes: ghc-soegtk-devel < 0.11-1, ghc-soegtk-doc < 0.11-1 +Obsoletes: ghc-svgcairo-devel < 0.11-1, ghc-svgcairo-doc < 0.11-1 +Obsoletes: ghc-vte-devel < 0.11-1, ghc-vte-doc < 0.11-1 BuildRequires: ghc, happy, ghc-rpm-macros >= 0.8.0 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel @@ -96,6 +109,19 @@ Group: Development/Libraries Requires: %{name} = %{version}-%{release} Obsoletes: ghc-haddock-prof < 2.4.2-3 Obsoletes: ghc-time-prof < 1.1.2.4-5 +# gtk2hs +Obsoletes: ghc-cairo-prof < 0.11-1 +Obsoletes: ghc-gconf-prof < 0.11-1 +Obsoletes: ghc-gio-prof < 0.11-1 +Obsoletes: ghc-glade-prof < 0.11-1 +Obsoletes: ghc-glib-prof < 0.11-1 +Obsoletes: ghc-gstreamer-prof < 0.11-1 +Obsoletes: ghc-gtk-prof < 0.11-1 +Obsoletes: ghc-gtkglext-prof < 0.11-1 +Obsoletes: ghc-gtksourceview2-prof < 0.11-1 +Obsoletes: ghc-soegtk-prof < 0.11-1 +Obsoletes: ghc-svgcairo-prof < 0.11-1 +Obsoletes: ghc-vte-prof < 0.11-1 %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -278,6 +304,9 @@ fi %endif %changelog +* Fri Jul 30 2010 Jens Petersen - 6.12.3-5 +- obsolete old gtk2hs packages for smooth upgrades + * Thu Jul 15 2010 Jens Petersen - 6.12.3-4 - merge ghc-doc into base package - obsolete ghc-time and ghc-ghc-doc (ghc-rpm-macros-0.8.0) From 9d63a496e3e93d60138e3d49d4e3b07be4437095 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 13 Sep 2010 13:40:56 +1000 Subject: [PATCH 169/530] add xmobar to pkg-deps.sh and ignore ghc-rpm-macros --- pkg-deps.sh | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index f20e0ae..045b691 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,7 +13,7 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too -for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hedgewars hscolour kaya xmonad; do +for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hedgewars hscolour kaya xmobar xmonad; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no if [ "$PKG_THERE" = "yes" ]; then @@ -30,7 +30,7 @@ for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-plat done # make sure all libs there -rpm -qa --qf "\"%{name}-%{version}\"\n" ghc-\* | egrep -v -- "(ghc-libs|-prof|-devel|-doc)-" | sed -e s/^\"ghc-/\"/g >> pkgs.dot +rpm -qa --qf "\"%{name}-%{version}\"\n" ghc-\* | egrep -v -- "(ghc-libs|-prof|-devel|-doc|rpm-macros)-" | sed -e s/^\"ghc-/\"/g >> pkgs.dot # and add it back echo "}" >> pkgs.dot From 6453beb234f4001b7b8eb1166b859878afa831f5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Sep 2010 12:23:10 +1000 Subject: [PATCH 170/530] pkg-deps.sh: drop hedgewars and kaya, and add warning for missing bin packages --- pkg-deps.sh | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 045b691..801f0c0 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,9 +13,9 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too -for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hedgewars hscolour kaya xmobar xmonad; do +for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hscolour xmobar xmonad; do PKG_THERE=yes - PKG=`rpm -q --qf "%{name}-%{version}" $i` || PKG_THERE=no + PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing $i" ; } if [ "$PKG_THERE" = "yes" ]; then echo \"$PKG\" >> pkgs.dot case $i in From 96dece0e90a1692441e047f03682c2a5be6ca563 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Sep 2010 12:35:22 +1000 Subject: [PATCH 171/530] pkg-deps.sh: check for graphviz --- pkg-deps.sh | 1 + 1 file changed, 1 insertion(+) diff --git a/pkg-deps.sh b/pkg-deps.sh index 801f0c0..8df293f 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -41,6 +41,7 @@ cp -p pkgs.dot pkgs.dot.orig GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done +which tred >/dev/null cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg if [ -n "$DISPLAY" ]; then From a90b89c92ac98d5414fabb3e8a25a972d0e7b35f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Sep 2010 12:44:42 +1000 Subject: [PATCH 172/530] pkg-deps.sh: comment list binlib progs and warn about missing graphviz --- pkg-deps.sh | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 8df293f..4f2261a 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -13,7 +13,8 @@ cd .pkg-deps ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too -for i in alex cabal-install cpphs darcs ghc happy gtk2hs-buildtools haskell-platform hscolour xmobar xmonad; do +# (exclude binlib for now since covered by libs): cpphs, darcs, hlint, hscolour, xmonad +for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform xmobar; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing $i" ; } if [ "$PKG_THERE" = "yes" ]; then @@ -41,7 +42,7 @@ cp -p pkgs.dot pkgs.dot.orig GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done -which tred >/dev/null +which tred &>/dev/null || { echo Please install graphviz ; exit 1 ; } cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg if [ -n "$DISPLAY" ]; then From 06db986bc221ed84aa56bdbc0ffacea62a313b56 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Sep 2010 18:21:06 +1000 Subject: [PATCH 173/530] move gtk2hs obsoletes to ghc-glib and ghc-gtk --- ghc.spec | 33 +++++---------------------------- 1 file changed, 5 insertions(+), 28 deletions(-) diff --git a/ghc.spec b/ghc.spec index b6d3d5c..5554787 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # part of haskell-platform-2010.2.0.0 Version: 6.12.3 -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -50,20 +50,7 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f14 Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 -# until new cabalized gtk2hs packages in f14+ -Obsoletes: ghc-cairo-devel < 0.11-1, ghc-cairo-doc < 0.11-1 -Obsoletes: ghc-gconf-devel < 0.11-1, ghc-gconf-doc < 0.11-1 -Obsoletes: ghc-gio-devel < 0.11-1, ghc-gio-doc < 0.11-1 -Obsoletes: ghc-glade-devel < 0.11-1, ghc-glade-doc < 0.11-1 -Obsoletes: ghc-glib-devel < 0.11-1, ghc-glib-doc < 0.11-1 -Obsoletes: ghc-gstreamer-devel < 0.11-1, ghc-gstreamer-doc < 0.11-1 -Obsoletes: ghc-gtk-devel < 0.11-1, ghc-gtk-doc < 0.11-1 -Obsoletes: ghc-gtkglext-devel < 0.11-1, ghc-gtkglext-doc < 0.11-1 -Obsoletes: ghc-gtksourceview2-devel < 0.11-1, ghc-gtksourceview2-doc < 0.11-1 -Obsoletes: ghc-soegtk-devel < 0.11-1, ghc-soegtk-doc < 0.11-1 -Obsoletes: ghc-svgcairo-devel < 0.11-1, ghc-svgcairo-doc < 0.11-1 -Obsoletes: ghc-vte-devel < 0.11-1, ghc-vte-doc < 0.11-1 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.8.0 +BuildRequires: ghc, happy, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -109,19 +96,6 @@ Group: Development/Libraries Requires: %{name} = %{version}-%{release} Obsoletes: ghc-haddock-prof < 2.4.2-3 Obsoletes: ghc-time-prof < 1.1.2.4-5 -# gtk2hs -Obsoletes: ghc-cairo-prof < 0.11-1 -Obsoletes: ghc-gconf-prof < 0.11-1 -Obsoletes: ghc-gio-prof < 0.11-1 -Obsoletes: ghc-glade-prof < 0.11-1 -Obsoletes: ghc-glib-prof < 0.11-1 -Obsoletes: ghc-gstreamer-prof < 0.11-1 -Obsoletes: ghc-gtk-prof < 0.11-1 -Obsoletes: ghc-gtkglext-prof < 0.11-1 -Obsoletes: ghc-gtksourceview2-prof < 0.11-1 -Obsoletes: ghc-soegtk-prof < 0.11-1 -Obsoletes: ghc-svgcairo-prof < 0.11-1 -Obsoletes: ghc-vte-prof < 0.11-1 %description prof Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). @@ -304,6 +278,9 @@ fi %endif %changelog +* Thu Sep 30 2010 Jens Petersen - 6.12.3-6 +- move gtk2hs obsoletes to ghc-glib and ghc-gtk + * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From 1a8d8453cb8187189cea7b6ecad0649178ebe234 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Sep 2010 17:57:22 +1000 Subject: [PATCH 174/530] better missing graphviz message --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 4f2261a..d3b1d1e 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -42,7 +42,7 @@ cp -p pkgs.dot pkgs.dot.orig GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done -which tred &>/dev/null || { echo Please install graphviz ; exit 1 ; } +which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg if [ -n "$DISPLAY" ]; then From eee7703e71e9f11aa67cb3e5f5c3deedd2474fcf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Sep 2010 19:18:00 +1000 Subject: [PATCH 175/530] drop happy buildrequires --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5554787..739b428 100644 --- a/ghc.spec +++ b/ghc.spec @@ -50,7 +50,7 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f14 Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 -BuildRequires: ghc, happy, ghc-rpm-macros >= 0.8.2 +BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel Requires: gcc, gmp-devel %if %{with shared} @@ -280,6 +280,7 @@ fi %changelog * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk +- drop happy buildrequires * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From 9248029847e256d41424be5e7c8ecd40cd9fd0c1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Sep 2010 19:22:52 +1000 Subject: [PATCH 176/530] try smp build again --- ghc.spec | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 739b428..d17113e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -144,8 +144,8 @@ export CFLAGS="${CFLAGS:-%optflags}" %{?with_shared:--enable-shared} # 8 cpus seems to break build -#make %{_smp_mflags} -make +make %{_smp_mflags} +#make %install rm -rf $RPM_BUILD_ROOT @@ -281,6 +281,7 @@ fi * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk - drop happy buildrequires +- try smp build again * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From ae79e78b92272845d6f44477969d59f4e5e78f3a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Oct 2010 13:57:32 +1000 Subject: [PATCH 177/530] smp build with max 4 cpus --- ghc.spec | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index d17113e..243e892 100644 --- a/ghc.spec +++ b/ghc.spec @@ -144,8 +144,9 @@ export CFLAGS="${CFLAGS:-%optflags}" %{?with_shared:--enable-shared} # 8 cpus seems to break build +RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) +[ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 make %{_smp_mflags} -#make %install rm -rf $RPM_BUILD_ROOT @@ -281,7 +282,7 @@ fi * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk - drop happy buildrequires -- try smp build again +- smp build with max 4 cpus * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From 3e0293d96eda4becbd88b92c215b12bbf4ac1828 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Oct 2010 14:33:11 +1000 Subject: [PATCH 178/530] 4 cpu build broke: make max smp 2 cpus --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 243e892..e4337bd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -143,9 +143,9 @@ export CFLAGS="${CFLAGS:-%optflags}" --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ %{?with_shared:--enable-shared} -# 8 cpus seems to break build +# 4 cpus or more sometimes breaks build RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) -[ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 +[ "$RPM_BUILD_NCPUS" -gt 2 ] && RPM_BUILD_NCPUS=2 make %{_smp_mflags} %install @@ -282,7 +282,7 @@ fi * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk - drop happy buildrequires -- smp build with max 4 cpus +- smp build with max 2 cpus * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From 0b9fb54ac7602e0b0b9db1899ded0952f89fa70e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Oct 2010 14:49:38 +1000 Subject: [PATCH 179/530] export RPM_BUILD_NCPUS to make --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index e4337bd..73b3ba8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -146,6 +146,7 @@ export CFLAGS="${CFLAGS:-%optflags}" # 4 cpus or more sometimes breaks build RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) [ "$RPM_BUILD_NCPUS" -gt 2 ] && RPM_BUILD_NCPUS=2 +export RPM_BUILD_NCPUS make %{_smp_mflags} %install From 6d2a942bcbeeee31883d9ecccfa2b127731b7c3e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Oct 2010 16:21:16 +1000 Subject: [PATCH 180/530] try again to fix smp build to no more than 4 cpus --- ghc.spec | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 73b3ba8..0176b13 100644 --- a/ghc.spec +++ b/ghc.spec @@ -144,10 +144,9 @@ export CFLAGS="${CFLAGS:-%optflags}" %{?with_shared:--enable-shared} # 4 cpus or more sometimes breaks build -RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) -[ "$RPM_BUILD_NCPUS" -gt 2 ] && RPM_BUILD_NCPUS=2 -export RPM_BUILD_NCPUS -make %{_smp_mflags} +[ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) +[ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 +make -j$RPM_BUILD_NCPUS %install rm -rf $RPM_BUILD_ROOT @@ -283,7 +282,7 @@ fi * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk - drop happy buildrequires -- smp build with max 2 cpus +- smp build with max 4 cpus * Fri Jul 30 2010 Jens Petersen - 6.12.3-5 - obsolete old gtk2hs packages for smooth upgrades From 43cebbc1fd646634a904c312db1643f3a35c7953 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 4 Nov 2010 16:48:25 +1000 Subject: [PATCH 181/530] skip huge type-level docs from haddock re-indexing (#649228) --- ghc-gen_contents_index-type-level.patch | 12 ++++++++++++ ghc.spec | 8 +++++++- 2 files changed, 19 insertions(+), 1 deletion(-) create mode 100644 ghc-gen_contents_index-type-level.patch diff --git a/ghc-gen_contents_index-type-level.patch b/ghc-gen_contents_index-type-level.patch new file mode 100644 index 0000000..05a9e42 --- /dev/null +++ b/ghc-gen_contents_index-type-level.patch @@ -0,0 +1,12 @@ +diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_contents_index +--- ghc-6.12.3/libraries/gen_contents_index~ 2010-09-14 13:03:12.000000000 +1000 ++++ ghc-6.12.3/libraries/gen_contents_index 2010-11-04 16:41:32.000000000 +1000 +@@ -24,7 +24,7 @@ + *) + HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index +- HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` ++ HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | grep -v '/type-level\.haddock' | sort` + for HADDOCK_FILE in $HADDOCK_FILES + do + NAME_VERSION=`echo "$HADDOCK_FILE" | sed 's#/.*##'` diff --git a/ghc.spec b/ghc.spec index 0176b13..7465482 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # part of haskell-platform-2010.2.0.0 Version: 6.12.3 -Release: 6%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -68,6 +68,7 @@ BuildRequires: hscolour BuildRequires: python %endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch +Patch2: ghc-gen_contents_index-type-level.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -110,6 +111,8 @@ They should be installed when GHC's profiling subsystem is needed. %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig +# type-level too big so skip it in gen_contents_index +%patch2 -p1 # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -279,6 +282,9 @@ fi %endif %changelog +* Thu Nov 4 2010 Jens Petersen - 6.12.3-7 +- skip huge type-level docs from haddock re-indexing (#649228) + * Thu Sep 30 2010 Jens Petersen - 6.12.3-6 - move gtk2hs obsoletes to ghc-glib and ghc-gtk - drop happy buildrequires From 60d9f57f31dbc17a93faeabf5c04df15372ecd1e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 4 Nov 2010 18:41:32 +1000 Subject: [PATCH 182/530] add a cronjob for haddock indexing and disable gen_contents_index by default gen_contents_index is run with --batch by cronjob, otherwise does nothing. This avoids overhead of running of re-indexing each time a ghc-*-devel package is installed, updated, or removed. --- ghc-doc-index.cron | 39 +++++++++++++++++++++++++ ghc-gen_contents_index-cron-batch.patch | 23 +++++++++++++++ ghc.spec | 15 +++++++++- 3 files changed, 76 insertions(+), 1 deletion(-) create mode 100755 ghc-doc-index.cron create mode 100644 ghc-gen_contents_index-cron-batch.patch diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron new file mode 100755 index 0000000..b9c5b3c --- /dev/null +++ b/ghc-doc-index.cron @@ -0,0 +1,39 @@ +#! /bin/bash + +if [ -e /etc/sysconfig/ghc-doc-index ]; then + . /etc/sysconfig/ghc-doc-index +fi + +if [ "$CRON" = "no" ]; then + exit 0 +fi + + +LOCKFILE=/var/lock/ghc-doc-index.lock + +# the lockfile is not meant to be perfect, it's just in case the +# two man-db cron scripts get run close to each other to keep +# them from stepping on each other's toes. The worst that will +# happen is that they will temporarily corrupt the database +[ -f $LOCKFILE ] && exit 0 + +trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT +touch $LOCKFILE + +# only re-index ghc docs when there are changes +cd /usr/share/doc/ghc/html/libraries +if [ -r .pkg-dir.cache ]; then + ls -d */ > .pkg-dir.cache.new + DIR_DIFF=$(diff .pkg-dir.cache .pkg-dir.cache.new) +else + ls -d */ > .pkg-dir.cache +fi +if [ -x "gen_contents_index" -a ! -r ".pkg-dir.cache.new" -o -n "$DIR_DIFF" ]; then + ./gen_contents_index --batch +fi + +if [ -f .pkg-dir.cache.new ]; then + mv -f .pkg-dir.cache{.new,} +fi + +exit 0 diff --git a/ghc-gen_contents_index-cron-batch.patch b/ghc-gen_contents_index-cron-batch.patch new file mode 100644 index 0000000..d3f0a53 --- /dev/null +++ b/ghc-gen_contents_index-cron-batch.patch @@ -0,0 +1,23 @@ +diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_contents_index +--- ghc-6.12.3/libraries/gen_contents_index~ 2010-09-14 13:03:12.000000000 +1000 ++++ ghc-6.12.3/libraries/gen_contents_index 2010-11-04 18:26:00.000000000 +1000 +@@ -21,6 +21,6 @@ + HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" + done + ;; +-*) ++--batch) + HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index +@@ -32,6 +32,9 @@ + HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" + done + ;; ++ *) ++ HADDOCK=/bin/true ++ tty -s && echo Run with '--batch' to index package haddock docs. + esac + + # Now create the combined contents and index pages + +Diff finished. Thu Nov 4 18:26:04 2010 diff --git a/ghc.spec b/ghc.spec index 7465482..5f5d260 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Name: ghc # part of haskell-platform-2010.2.0.0 Version: 6.12.3 -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -39,6 +39,7 @@ Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs %if %{with testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 %endif +Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f14 @@ -69,6 +70,7 @@ BuildRequires: python %endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch +Patch3: ghc-gen_contents_cron-batch.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -113,6 +115,8 @@ They should be installed when GHC's profiling subsystem is needed. %patch1 -p1 -b .orig # type-level too big so skip it in gen_contents_index %patch2 -p1 +# disable gen_contents_index when not --batch for cron +%patch3 -p1 # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -190,6 +194,10 @@ done %ghc_strip_dynlinked +%if %{with doc} +mkdir -p %{_sysconfdir}/cron.hourly +install -p --mode=755 %SOURCE3 %{_sysconfdir}/cron.hourly/ghc-doc-index +%endif %check # stolen from ghc6/debian/rules: @@ -269,6 +277,7 @@ fi %ghost %{ghcdocbasedir}/libraries/index*.html %ghost %{ghcdocbasedir}/libraries/minus.gif %ghost %{ghcdocbasedir}/libraries/plus.gif +%{_sysconfdir}/cron.hourly/ghc-doc-index %endif %if %{with shared} @@ -282,6 +291,10 @@ fi %endif %changelog +* Thu Nov 4 2010 Jens Petersen - 6.12.3-8 +- add a cronjob for doc indexing +- disable gen_contents_index when not run with --batch for cron + * Thu Nov 4 2010 Jens Petersen - 6.12.3-7 - skip huge type-level docs from haddock re-indexing (#649228) From 99bc2d8605d23dcd696c50236140441216dfb77e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 4 Nov 2010 18:50:53 +1000 Subject: [PATCH 183/530] fix the name of the --batch patch --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5f5d260..226ee6f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -70,7 +70,7 @@ BuildRequires: python %endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch -Patch3: ghc-gen_contents_cron-batch.patch +Patch3: ghc-gen_contents_index-cron-batch.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely From afb7c9827eae84f2acf5bcab65251dae7a9c1a6a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Nov 2010 11:25:54 +1000 Subject: [PATCH 184/530] fix ghc-gen_contents_index-cron-batch.patch so that it applies --- ghc-gen_contents_index-cron-batch.patch | 13 ++++++------- 1 file changed, 6 insertions(+), 7 deletions(-) diff --git a/ghc-gen_contents_index-cron-batch.patch b/ghc-gen_contents_index-cron-batch.patch index d3f0a53..fdade1a 100644 --- a/ghc-gen_contents_index-cron-batch.patch +++ b/ghc-gen_contents_index-cron-batch.patch @@ -1,7 +1,7 @@ -diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_contents_index ---- ghc-6.12.3/libraries/gen_contents_index~ 2010-09-14 13:03:12.000000000 +1000 -+++ ghc-6.12.3/libraries/gen_contents_index 2010-11-04 18:26:00.000000000 +1000 -@@ -21,6 +21,6 @@ +diff -u ghc-6.12.3/libraries/gen_contents_index gen_contents_index +--- ghc-6.12.3/libraries/gen_contents_index 2010-11-05 10:28:02.000000000 +1000 ++++ gen_contents_index 2010-11-05 10:20:37.000000000 +1000 +@@ -21,7 +21,7 @@ HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" done ;; @@ -9,15 +9,14 @@ diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_conte +--batch) HADDOCK=/usr/bin/haddock # We don't want the GHC API to swamp the index + HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | grep -v '/type-level\.haddock' | sort` @@ -32,6 +32,9 @@ HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" done ;; -+ *) ++*) + HADDOCK=/bin/true + tty -s && echo Run with '--batch' to index package haddock docs. esac # Now create the combined contents and index pages - -Diff finished. Thu Nov 4 18:26:04 2010 From b2f46c4721ab9a11af8d683323d776dc45310738 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Nov 2010 11:33:43 +1000 Subject: [PATCH 185/530] use system libffi with ghc-use-system-libffi-debian.patch --- ghc-use-system-libffi-debian.patch | 110 +++++++++++++++++++++++++++++ ghc.spec | 11 +-- 2 files changed, 117 insertions(+), 4 deletions(-) create mode 100644 ghc-use-system-libffi-debian.patch diff --git a/ghc-use-system-libffi-debian.patch b/ghc-use-system-libffi-debian.patch new file mode 100644 index 0000000..7284553 --- /dev/null +++ b/ghc-use-system-libffi-debian.patch @@ -0,0 +1,110 @@ +Index: ghc6-6.12.3/ghc.mk +=================================================================== +--- ghc6-6.12.3.orig/ghc.mk 2010-06-09 21:10:12.000000000 +0300 ++++ ghc6-6.12.3/ghc.mk 2010-07-17 11:52:25.000000000 +0300 +@@ -369,11 +369,6 @@ + endif + BOOT_LIBS = $(foreach lib,$(BOOT_PKGS),$(libraries/$(lib)_dist-boot_v_LIB)) + +-OTHER_LIBS = libffi/dist-install/build/libHSffi$(v_libsuf) libffi/dist-install/build/HSffi.o +-ifeq "$(BuildSharedLibs)" "YES" +-OTHER_LIBS += libffi/dist-install/build/libHSffi$(dyn_libsuf) +-endif +- + # We cannot run ghc-cabal to configure a package until we have + # configured and registered all of its dependencies. So the following + # hack forces all the configure steps to happen in exactly the order +@@ -406,7 +401,6 @@ + # add the final two package.conf dependencies: ghc-prim depends on RTS, + # and RTS depends on libffi. + libraries/ghc-prim/dist-install/package-data.mk : rts/package.conf.inplace +-rts/package.conf.inplace : libffi/package.conf.inplace + endif + + # ----------------------------------------------------------------------------- +@@ -518,7 +512,6 @@ + driver \ + driver/ghci \ + driver/ghc \ +- libffi \ + includes \ + rts + +@@ -863,11 +856,10 @@ + $(addprefix libraries/,$(PACKAGES_STAGE2)) + + install_packages: install_libexecs +-install_packages: libffi/package.conf.install rts/package.conf.install ++install_packages: rts/package.conf.install + $(INSTALL_DIR) "$(DESTDIR)$(topdir)" + "$(RM)" -r $(RM_OPTS) "$(INSTALLED_PACKAGE_CONF)" + $(INSTALL_DIR) "$(INSTALLED_PACKAGE_CONF)" +- "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update libffi/package.conf.install + "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install + $(foreach p, $(ALL_INSTALLED_PACKAGES),\ + "$(GHC_CABAL_INPLACE)" install \ +@@ -942,7 +934,7 @@ + unix-binary-dist-prep: + "$(RM)" $(RM_OPTS) -r bindistprep/ + "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) +- set -e; for i in LICENSE compiler ghc rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done ++ set -e; for i in LICENSE compiler ghc rts libraries utils docs includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done + echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) + echo "LATEX_DOCS = $(LATEX_DOCS)" >> $(BIN_DIST_MK) + echo "BUILD_DOCBOOK_HTML = $(BUILD_DOCBOOK_HTML)" >> $(BIN_DIST_MK) +@@ -1020,7 +1012,7 @@ + # + # Files to include in source distributions + # +-SRC_DIST_DIRS = mk rules docs distrib bindisttest libffi includes utils docs rts compiler ghc driver libraries ghc-tarballs ++SRC_DIST_DIRS = mk rules docs distrib bindisttest includes utils docs rts compiler ghc driver libraries ghc-tarballs + SRC_DIST_FILES += \ + configure.ac config.guess config.sub configure \ + aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \ +Index: ghc6-6.12.3/rts/ghc.mk +=================================================================== +--- ghc6-6.12.3.orig/rts/ghc.mk 2010-06-09 21:10:14.000000000 +0300 ++++ ghc6-6.12.3/rts/ghc.mk 2010-07-17 11:52:25.000000000 +0300 +@@ -333,15 +333,13 @@ + + $(eval $(call build-dependencies,rts,dist,1)) + +-$(rts_dist_depfile) : libffi/dist-install/build/ffi.h +- + #----------------------------------------------------------------------------- + # libffi stuff + +-rts_CC_OPTS += -Ilibffi/build/include +-rts_HC_OPTS += -Ilibffi/build/include +-rts_HSC2HS_OPTS += -Ilibffi/build/include +-rts_LD_OPTS += -Llibffi/build/include ++rts_CC_OPTS += $(shell pkg-config --cflags libffi) ++rts_HC_OPTS += $(shell pkg-config --cflags libffi) ++rts_HSC2HS_OPTS += $(shell pkg-config --cflags libffi) ++rts_LD_OPTS += $(shell pkg-config --libs libffi) + + # ----------------------------------------------------------------------------- + # compile generic patchable dyn-wrapper +Index: ghc6-6.12.3/rts/package.conf.in +=================================================================== +--- ghc6-6.12.3.orig/rts/package.conf.in 2010-06-09 21:10:14.000000000 +0300 ++++ ghc6-6.12.3/rts/package.conf.in 2010-07-17 11:53:57.000000000 +0300 +@@ -28,8 +28,9 @@ + hs-libraries: "HSrts" + + extra-libraries: ++ "ffi" + #ifdef HAVE_LIBM +- "m" /* for ldexp() */ ++ , "m" /* for ldexp() */ + #endif + #ifdef HAVE_LIBRT + , "rt" +@@ -59,7 +60,6 @@ + #endif + + includes: Stg.h +-depends: builtin_ffi + hugs-options: + cc-options: + diff --git a/ghc.spec b/ghc.spec index 226ee6f..1e8fd71 100644 --- a/ghc.spec +++ b/ghc.spec @@ -53,10 +53,9 @@ Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel +BuildRequires: libffi-devel Requires: gcc, gmp-devel %if %{with shared} -# not sure if this is actually needed: -BuildRequires: libffi-devel Requires: %{name}-libs = %{version}-%{release} %endif %if %{with manual} @@ -71,6 +70,7 @@ BuildRequires: python Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch +Patch4: ghc-use-system-libffi-debian.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -117,9 +117,11 @@ They should be installed when GHC's profiling subsystem is needed. %patch2 -p1 # disable gen_contents_index when not --batch for cron %patch3 -p1 +# use system libffi +%patch4 -p1 -b .libffi -# make sure we don't use these -rm -r ghc-tarballs/{mingw,perl} +# prefer system libraries +rm -r ghc-tarballs %build cat > mk/build.mk << EOF @@ -294,6 +296,7 @@ fi * Thu Nov 4 2010 Jens Petersen - 6.12.3-8 - add a cronjob for doc indexing - disable gen_contents_index when not run with --batch for cron +- use system libffi with ghc-use-system-libffi-debian.patch * Thu Nov 4 2010 Jens Petersen - 6.12.3-7 - skip huge type-level docs from haddock re-indexing (#649228) From fc933444ede06bf606bf69cb1a1eb72a1c5ff106 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Nov 2010 18:28:54 +1000 Subject: [PATCH 186/530] add bcond for system libffi and fix system libffi build - rename ghc-use-system-libffi-debian.patch to ghc-use-system-libffi.patch. - add ffi to SRC_HC_OPTS - use pkgconfig-depends in compiler/ghc.cabal for libffi --- ...i-debian.patch => ghc-use-system-libffi.patch | 12 ++++++++++++ ghc.spec | 16 +++++++++++++--- 2 files changed, 25 insertions(+), 3 deletions(-) rename ghc-use-system-libffi-debian.patch => ghc-use-system-libffi.patch (90%) diff --git a/ghc-use-system-libffi-debian.patch b/ghc-use-system-libffi.patch similarity index 90% rename from ghc-use-system-libffi-debian.patch rename to ghc-use-system-libffi.patch index 7284553..04ecde7 100644 --- a/ghc-use-system-libffi-debian.patch +++ b/ghc-use-system-libffi.patch @@ -108,3 +108,15 @@ Index: ghc6-6.12.3/rts/package.conf.in hugs-options: cc-options: +diff -u ghc-6.12.3/compiler/ghc.cabal.in\~ ghc-6.12.3/compiler/ghc.cabal.in +--- ghc-6.12.3/compiler/ghc.cabal.in~ 2010-06-10 04:10:09.000000000 +1000 ++++ ghc-6.12.3/compiler/ghc.cabal.in 2010-11-05 18:08:11.000000000 +1000 +@@ -83,7 +83,7 @@ + if flag(ghci) + Build-Depends: template-haskell + CPP-Options: -DGHCI +- Include-Dirs: ../libffi/build/include ++ pkgconfig-depends: libffi + + if !flag(ncg) + CPP-Options: -DOMIT_NATIVE_CODEGEN diff --git a/ghc.spec b/ghc.spec index 1e8fd71..b9de313 100644 --- a/ghc.spec +++ b/ghc.spec @@ -13,6 +13,8 @@ %bcond_without testsuite # include colored html src %bcond_without hscolour +# use system libffi +%bcond_without libffi ## default disabled options ## # include extralibs @@ -53,7 +55,9 @@ Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel +%if %{with libffi} BuildRequires: libffi-devel +%endif Requires: gcc, gmp-devel %if %{with shared} Requires: %{name}-libs = %{version}-%{release} @@ -70,7 +74,7 @@ BuildRequires: python Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch -Patch4: ghc-use-system-libffi-debian.patch +Patch4: ghc-use-system-libffi.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -118,9 +122,11 @@ They should be installed when GHC's profiling subsystem is needed. # disable gen_contents_index when not --batch for cron %patch3 -p1 # use system libffi +%if %{with libffi} %patch4 -p1 -b .libffi +%endif -# prefer system libraries +# use system libraries rm -r ghc-tarballs %build @@ -142,6 +148,9 @@ SplitObjs = NO %if %{without hscolour} HSCOLOUR_SRCS = NO %endif +%if %{with libffi} +SRC_HC_OPTS += -lffi +%endif EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -296,7 +305,8 @@ fi * Thu Nov 4 2010 Jens Petersen - 6.12.3-8 - add a cronjob for doc indexing - disable gen_contents_index when not run with --batch for cron -- use system libffi with ghc-use-system-libffi-debian.patch +- use system libffi with ghc-use-system-libffi.patch from debian +- add bcond for system libffi * Thu Nov 4 2010 Jens Petersen - 6.12.3-7 - skip huge type-level docs from haddock re-indexing (#649228) From b9392a129a659c0301bbb5c8f453b08a015b9336 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Nov 2010 19:00:40 +1000 Subject: [PATCH 187/530] prefix cronjob path with buildroot --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index b9de313..102d800 100644 --- a/ghc.spec +++ b/ghc.spec @@ -206,8 +206,8 @@ done %ghc_strip_dynlinked %if %{with doc} -mkdir -p %{_sysconfdir}/cron.hourly -install -p --mode=755 %SOURCE3 %{_sysconfdir}/cron.hourly/ghc-doc-index +mkdir -p ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly +install -p --mode=755 %SOURCE3 ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly/ghc-doc-index %endif %check From 04b53a4dd943b93ac0fe1c03b5189cef4b0891c9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Nov 2010 21:14:26 +1000 Subject: [PATCH 188/530] simplify ghc-gen_contents_index-cron-batch.patch case context --- ghc-gen_contents_index-cron-batch.patch | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/ghc-gen_contents_index-cron-batch.patch b/ghc-gen_contents_index-cron-batch.patch index fdade1a..9e30974 100644 --- a/ghc-gen_contents_index-cron-batch.patch +++ b/ghc-gen_contents_index-cron-batch.patch @@ -1,15 +1,13 @@ diff -u ghc-6.12.3/libraries/gen_contents_index gen_contents_index --- ghc-6.12.3/libraries/gen_contents_index 2010-11-05 10:28:02.000000000 +1000 +++ gen_contents_index 2010-11-05 10:20:37.000000000 +1000 -@@ -21,7 +21,7 @@ - HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" +@@ -22,5 +22,5 @@ done ;; -*) +--batch) HADDOCK=/usr/bin/haddock # We don't want the GHC API to swamp the index - HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | grep -v '/type-level\.haddock' | sort` @@ -32,6 +32,9 @@ HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" done From 49c90fefbc6a20cf0f2249a85e486aa22aa95573 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 8 Nov 2010 10:40:15 +1000 Subject: [PATCH 189/530] disable the libffi changes since they broke libHSffi*.so --- ghc.spec | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 102d800..f9f0ba2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -13,14 +13,14 @@ %bcond_without testsuite # include colored html src %bcond_without hscolour -# use system libffi -%bcond_without libffi ## default disabled options ## # include extralibs %bcond_with extralibs # quick build profile %bcond_with quick +# use system libffi +%bcond_with libffi # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} @@ -28,7 +28,7 @@ Name: ghc # part of haskell-platform-2010.2.0.0 Version: 6.12.3 -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -302,6 +302,9 @@ fi %endif %changelog +* Mon Nov 8 2010 Jens Petersen - 6.12.3-9 +- disable the libffi changes for now since they break libHSffi*.so + * Thu Nov 4 2010 Jens Petersen - 6.12.3-8 - add a cronjob for doc indexing - disable gen_contents_index when not run with --batch for cron From da2d519cd60c57561d02d703791d7e92531d954a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 8 Nov 2010 10:57:01 +1000 Subject: [PATCH 190/530] need BR libffi-devel anyway --- ghc.spec | 2 -- 1 file changed, 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index f9f0ba2..5aa925a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -55,9 +55,7 @@ Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel -%if %{with libffi} BuildRequires: libffi-devel -%endif Requires: gcc, gmp-devel %if %{with shared} Requires: %{name}-libs = %{version}-%{release} From 898edc65df57ad4119455ef48062966064ca5b6d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 8 Nov 2010 11:12:12 +1000 Subject: [PATCH 191/530] use libffi bcond for the ghc-tarballs removal too --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5aa925a..f6121e8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -125,7 +125,10 @@ They should be installed when GHC's profiling subsystem is needed. %endif # use system libraries -rm -r ghc-tarballs +rm -r ghc-tarballs/{mingw,perl} +%if %{with libffi} +rm -r ghc-tarballs/libffi +%endif %build cat > mk/build.mk << EOF From d48549968c7056753887c246854f1369fb1878f8 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 16 Nov 2010 17:41:09 +1000 Subject: [PATCH 192/530] update to 7.0.1 and turn system libffi back on --- .gitignore | 2 ++ ghc.spec | 18 +++++++++++------- sources | 4 ++-- 3 files changed, 15 insertions(+), 9 deletions(-) diff --git a/.gitignore b/.gitignore index 4a3c164..435f172 100644 --- a/.gitignore +++ b/.gitignore @@ -1,2 +1,4 @@ ghc-6.12.3-src.tar.bz2 testsuite-6.12.3.tar.bz2 +/ghc-7.0.1-src.tar.bz2 +/testsuite-7.0.1.tar.bz2 diff --git a/ghc.spec b/ghc.spec index f6121e8..505ecbf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -13,22 +13,22 @@ %bcond_without testsuite # include colored html src %bcond_without hscolour +# use system libffi +%bcond_without libffi ## default disabled options ## # include extralibs %bcond_with extralibs # quick build profile %bcond_with quick -# use system libffi -%bcond_with libffi # the debuginfo subpackage is currently empty anyway, so don't generate it %global debug_package %{nil} Name: ghc -# part of haskell-platform-2010.2.0.0 -Version: 6.12.3 -Release: 9%{?dist} +# breaks haskell-platform-2010.2.0.0 +Version: 7.0.1 +Release: 1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -57,6 +57,7 @@ BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 BuildRequires: gmp-devel, ncurses-devel BuildRequires: libffi-devel Requires: gcc, gmp-devel +# llvm is an optional dependency %if %{with shared} Requires: %{name}-libs = %{version}-%{release} %endif @@ -280,12 +281,11 @@ fi %{ghcdocbasedir}/libraries/frames.html %{ghcdocbasedir}/libraries/gen_contents_index %{ghcdocbasedir}/libraries/hscolour.css +%{ghcdocbasedir}/libraries/ocean.css %{ghcdocbasedir}/libraries/prologue.txt %{ghcdocbasedir}/index.html %ghost %{ghcdocbasedir}/libraries/doc-index*.html -%ghost %{ghcdocbasedir}/libraries/haddock.css %ghost %{ghcdocbasedir}/libraries/haddock-util.js -%ghost %{ghcdocbasedir}/libraries/haskell_icon.gif %ghost %{ghcdocbasedir}/libraries/index*.html %ghost %{ghcdocbasedir}/libraries/minus.gif %ghost %{ghcdocbasedir}/libraries/plus.gif @@ -303,6 +303,10 @@ fi %endif %changelog +* Tue Nov 16 2010 Jens Petersen - 7.0.1-1 +- update to 7.0.1 release +- turn on system libffi again + * Mon Nov 8 2010 Jens Petersen - 6.12.3-9 - disable the libffi changes for now since they break libHSffi*.so diff --git a/sources b/sources index e7c5106..b3abffd 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -4c2663c2eff833d7b9f39ef770eefbd6 ghc-6.12.3-src.tar.bz2 -5c6143040d043f10e6d014cd5fd8ca36 testsuite-6.12.3.tar.bz2 +91814d1de48c661fd79ffa810026ed19 ghc-7.0.1-src.tar.bz2 +96ea44f9c0fe6552883e2aa129f3e701 testsuite-7.0.1.tar.bz2 From e9ad266662786d433a8073a70d6b10730b265202 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 16 Nov 2010 19:09:11 +1000 Subject: [PATCH 193/530] update ghc-use-system-libffi.patch for ghc-7.0.1 --- ghc-use-system-libffi.patch | 106 ++++++++++++++++++------------------ 1 file changed, 52 insertions(+), 54 deletions(-) diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index 04ecde7..31f40c6 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -1,58 +1,69 @@ -Index: ghc6-6.12.3/ghc.mk -=================================================================== ---- ghc6-6.12.3.orig/ghc.mk 2010-06-09 21:10:12.000000000 +0300 -+++ ghc6-6.12.3/ghc.mk 2010-07-17 11:52:25.000000000 +0300 -@@ -369,11 +369,6 @@ +diff -up ghc-7.0.1/compiler/ghc.cabal.in.libffi ghc-7.0.1/compiler/ghc.cabal.in +--- ghc-7.0.1/compiler/ghc.cabal.in.libffi 2010-11-13 04:10:03.000000000 +1000 ++++ ghc-7.0.1/compiler/ghc.cabal.in 2010-11-16 19:04:28.000000000 +1000 +@@ -83,7 +83,7 @@ Library + if flag(ghci) + Build-Depends: template-haskell + CPP-Options: -DGHCI +- Include-Dirs: ../libffi/build/include ++ pkgconfig-depends: libffi + + if !flag(ncg) + CPP-Options: -DOMIT_NATIVE_CODEGEN +diff -up ghc-7.0.1/ghc.mk.libffi ghc-7.0.1/ghc.mk +--- ghc-7.0.1/ghc.mk.libffi 2010-11-13 04:10:05.000000000 +1000 ++++ ghc-7.0.1/ghc.mk 2010-11-16 19:04:28.000000000 +1000 +@@ -437,7 +437,6 @@ utils/runghc/dist/package-data.mk: compi + # add the final two package.conf dependencies: ghc-prim depends on RTS, + # and RTS depends on libffi. + libraries/ghc-prim/dist-install/package-data.mk : rts/package.conf.inplace +-rts/package.conf.inplace : libffi/package.conf.inplace endif - BOOT_LIBS = $(foreach lib,$(BOOT_PKGS),$(libraries/$(lib)_dist-boot_v_LIB)) + + # -------------------------------- +@@ -452,11 +451,6 @@ ALL_STAGE1_LIBS += $(foreach lib,$(PACKA + endif + BOOT_LIBS = $(foreach lib,$(STAGE0_PACKAGES),$(libraries/$(lib)_dist-boot_v_LIB)) -OTHER_LIBS = libffi/dist-install/build/libHSffi$(v_libsuf) libffi/dist-install/build/HSffi.o -ifeq "$(BuildSharedLibs)" "YES" -OTHER_LIBS += libffi/dist-install/build/libHSffi$(dyn_libsuf) -endif - - # We cannot run ghc-cabal to configure a package until we have - # configured and registered all of its dependencies. So the following - # hack forces all the configure steps to happen in exactly the order -@@ -406,7 +401,6 @@ - # add the final two package.conf dependencies: ghc-prim depends on RTS, - # and RTS depends on libffi. - libraries/ghc-prim/dist-install/package-data.mk : rts/package.conf.inplace --rts/package.conf.inplace : libffi/package.conf.inplace - endif + # ---------------------------------------- + # Special magic for the ghc-prim package - # ----------------------------------------------------------------------------- -@@ -518,7 +512,6 @@ - driver \ +@@ -581,7 +575,6 @@ BUILD_DIRS += \ driver/ghci \ driver/ghc \ + driver/haddock \ - libffi \ includes \ rts -@@ -863,11 +856,10 @@ - $(addprefix libraries/,$(PACKAGES_STAGE2)) +@@ -937,11 +930,10 @@ INSTALL_DISTDIR_compiler = stage2 + # Now we can do the installation install_packages: install_libexecs -install_packages: libffi/package.conf.install rts/package.conf.install +install_packages: rts/package.conf.install $(INSTALL_DIR) "$(DESTDIR)$(topdir)" - "$(RM)" -r $(RM_OPTS) "$(INSTALLED_PACKAGE_CONF)" + "$(RM)" $(RM_OPTS_REC) "$(INSTALLED_PACKAGE_CONF)" $(INSTALL_DIR) "$(INSTALLED_PACKAGE_CONF)" - "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update libffi/package.conf.install "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install - $(foreach p, $(ALL_INSTALLED_PACKAGES),\ - "$(GHC_CABAL_INPLACE)" install \ -@@ -942,7 +934,7 @@ + $(foreach p, $(INSTALLED_PKG_DIRS), \ + $(call make-command, \ +@@ -1024,7 +1016,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindi unix-binary-dist-prep: - "$(RM)" $(RM_OPTS) -r bindistprep/ + "$(RM)" $(RM_OPTS_REC) bindistprep/ "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) -- set -e; for i in LICENSE compiler ghc rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done -+ set -e; for i in LICENSE compiler ghc rts libraries utils docs includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done +- set -e; for i in packages LICENSE compiler ghc rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done ++ set -e; for i in packages LICENSE compiler ghc rts libraries utils docs includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) echo "LATEX_DOCS = $(LATEX_DOCS)" >> $(BIN_DIST_MK) echo "BUILD_DOCBOOK_HTML = $(BUILD_DOCBOOK_HTML)" >> $(BIN_DIST_MK) -@@ -1020,7 +1012,7 @@ +@@ -1102,7 +1094,7 @@ SRC_DIST_DIR=$(shell pwd)/$(SRC_DIST_NAM # # Files to include in source distributions # @@ -61,16 +72,16 @@ Index: ghc6-6.12.3/ghc.mk SRC_DIST_FILES += \ configure.ac config.guess config.sub configure \ aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \ -Index: ghc6-6.12.3/rts/ghc.mk -=================================================================== ---- ghc6-6.12.3.orig/rts/ghc.mk 2010-06-09 21:10:14.000000000 +0300 -+++ ghc6-6.12.3/rts/ghc.mk 2010-07-17 11:52:25.000000000 +0300 -@@ -333,15 +333,13 @@ +diff -up ghc-7.0.1/rts/ghc.mk.libffi ghc-7.0.1/rts/ghc.mk +--- ghc-7.0.1/rts/ghc.mk.libffi 2010-11-13 04:10:06.000000000 +1000 ++++ ghc-7.0.1/rts/ghc.mk 2010-11-16 19:06:09.000000000 +1000 +@@ -430,15 +430,15 @@ endif $(eval $(call build-dependencies,rts,dist,1)) --$(rts_dist_depfile) : libffi/dist-install/build/ffi.h -- +-$(rts_dist_depfile_c_asm) : libffi/dist-install/build/ffi.h $(DTRACEPROBES_H) ++$(rts_dist_depfile_c_asm) : $(DTRACEPROBES_H) + #----------------------------------------------------------------------------- # libffi stuff @@ -84,12 +95,11 @@ Index: ghc6-6.12.3/rts/ghc.mk +rts_LD_OPTS += $(shell pkg-config --libs libffi) # ----------------------------------------------------------------------------- - # compile generic patchable dyn-wrapper -Index: ghc6-6.12.3/rts/package.conf.in -=================================================================== ---- ghc6-6.12.3.orig/rts/package.conf.in 2010-06-09 21:10:14.000000000 +0300 -+++ ghc6-6.12.3/rts/package.conf.in 2010-07-17 11:53:57.000000000 +0300 -@@ -28,8 +28,9 @@ + # compile dtrace probes if dtrace is supported +diff -up ghc-7.0.1/rts/package.conf.in.libffi ghc-7.0.1/rts/package.conf.in +--- ghc-7.0.1/rts/package.conf.in.libffi 2010-11-13 04:10:06.000000000 +1000 ++++ ghc-7.0.1/rts/package.conf.in 2010-11-16 19:04:28.000000000 +1000 +@@ -24,8 +24,9 @@ library-dirs: TOP"/rts/dist/build" PAPI hs-libraries: "HSrts" extra-libraries: @@ -100,7 +110,7 @@ Index: ghc6-6.12.3/rts/package.conf.in #endif #ifdef HAVE_LIBRT , "rt" -@@ -59,7 +60,6 @@ +@@ -55,7 +56,6 @@ include-dirs: TOP"/includes" #endif includes: Stg.h @@ -108,15 +118,3 @@ Index: ghc6-6.12.3/rts/package.conf.in hugs-options: cc-options: -diff -u ghc-6.12.3/compiler/ghc.cabal.in\~ ghc-6.12.3/compiler/ghc.cabal.in ---- ghc-6.12.3/compiler/ghc.cabal.in~ 2010-06-10 04:10:09.000000000 +1000 -+++ ghc-6.12.3/compiler/ghc.cabal.in 2010-11-05 18:08:11.000000000 +1000 -@@ -83,7 +83,7 @@ - if flag(ghci) - Build-Depends: template-haskell - CPP-Options: -DGHCI -- Include-Dirs: ../libffi/build/include -+ pkgconfig-depends: libffi - - if !flag(ncg) - CPP-Options: -DOMIT_NATIVE_CODEGEN From b8e43eda1e6ea0e5fdccee129b8fe8b3b707a8ae Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 23 Nov 2010 17:41:14 +1000 Subject: [PATCH 194/530] drop -o from ghc_binlib_package --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 505ecbf..73dd237 100644 --- a/ghc.spec +++ b/ghc.spec @@ -110,7 +110,7 @@ They should be installed when GHC's profiling subsystem is needed. %global ghc_version_override %{version} -%ghc_binlib_package -n ghc -o 6.12.3-4 +%ghc_binlib_package -n ghc %prep %setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} @@ -305,7 +305,7 @@ fi %changelog * Tue Nov 16 2010 Jens Petersen - 7.0.1-1 - update to 7.0.1 release -- turn on system libffi again +- turn on system libffi now * Mon Nov 8 2010 Jens Petersen - 6.12.3-9 - disable the libffi changes for now since they break libHSffi*.so From cb3dc6043b88612b01842620c320c0d4c19f6d0b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Nov 2010 00:41:15 +1000 Subject: [PATCH 195/530] require libffi-devel --- ghc.spec | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 73dd237..f9c4497 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,7 +28,7 @@ Name: ghc # breaks haskell-platform-2010.2.0.0 Version: 7.0.1 -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -54,9 +54,10 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-time-devel < 1.1.2.4-5 Obsoletes: ghc-time-doc < 1.1.2.4-5 BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 -BuildRequires: gmp-devel, ncurses-devel -BuildRequires: libffi-devel -Requires: gcc, gmp-devel +BuildRequires: gmp-devel, libffi-devel +# for internal terminfo +BuildRequires: ncurses-devel +Requires: gcc, gmp-devel, libffi-devel # llvm is an optional dependency %if %{with shared} Requires: %{name}-libs = %{version}-%{release} @@ -303,6 +304,9 @@ fi %endif %changelog +* Wed Nov 24 2010 Jens Petersen - 7.0.1-2 +- require libffi-devel + * Tue Nov 16 2010 Jens Petersen - 7.0.1-1 - update to 7.0.1 release - turn on system libffi now From 7799140415e66b899070b2a2c00221465ab03b25 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 30 Nov 2010 19:22:17 +1000 Subject: [PATCH 196/530] update pkg-deps.sh not to assume ghc6 --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index d3b1d1e..15bf088 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -24,7 +24,7 @@ for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform xmobar; rpm -q --requires $i | grep -v rpmlib | grep -v ghc | sed -e "s/^/\"$PKG\" -> \"/g" -e "s/ = \(.*\)/-\1\"/" >> pkgs.dot ;; *) - rpm -q --requires $i | grep ghc6 | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc6.*/\"/" >> pkgs.dot + rpm -q --requires $i | grep -- -ghc | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc.*/\"/" >> pkgs.dot ;; esac fi From 21a2961535a114340f8c6f9bfc996d8d02e85dac Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 4 Dec 2010 22:09:49 +1000 Subject: [PATCH 197/530] hackage-status.sh generate a Fedora distro file for hackage.haskell.org --- hackage-status.sh | 14 ++++++++++++++ 1 file changed, 14 insertions(+) create mode 100755 hackage-status.sh diff --git a/hackage-status.sh b/hackage-status.sh new file mode 100755 index 0000000..d62fad1 --- /dev/null +++ b/hackage-status.sh @@ -0,0 +1,14 @@ +#!/bin/sh + +# generates a Fedora distro package status file for hackage.haskell.org + +PKGS="ghc-Boolean ghc-GLUT ghc-HTTP ghc-HUnit ghc-OpenGL ghc-QuickCheck ghc-X11 ghc-X11-xft alex ghc-attoparsec ghc-base64-bytestring ghc-binary ghc-bytestring-trie cabal-install ghc-cairo ghc-cgi ghc-chalmers-lava2000 ghc-cmdargs ghc-colour cpphs ghc-csv darcs ghc-dataenc ghc-deepseq ghc-editline ghc-feldspar-language ghc-fgl ghc-ghc-paths ghc-gio ghc-glade ghc-glib ghc-gtk gtk2hs-buildtools ghc-gtksourceview2 happy ghc-hashed-storage ghc-haskeline ghc-haskell-src ghc-haskell-src-exts ghc-hinotify hlint ghc-hslogger hscolour ghc-html ghc-libmpd ghc-mmap ghc-mtl ghc-network ghc-pango ghc-parallel ghc-parsec ghc-regex-base ghc-regex-compat ghc-regex-posix ghc-regex-tdfa ghc-split ghc-stm ghc-syb ghc-tagsoup ghc-tar ghc-terminfo ghc-text ghc-transformers ghc-type-level ghc-uniplate ghc-utf8-string ghc-xhtml xmobar xmonad ghc-xmonad-contrib ghc-zlib" + +for p in $PKGS; do + LATEST=$(koji latest-pkg --quiet dist-rawhide $p | cut -f1 -d' ' | sed -e "s/\(.*\)-.*/\1/") + HACKAGE=$(echo $p | sed -e "s/^ghc-//") + VERSION=$(echo $LATEST | sed -e "s/^$p-//") + if [ -n "$VERSION" ]; then + echo "(\"$HACKAGE\",\"$VERSION\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/$p\")" + fi +done From 125772e66204c0e02998cba4f881c71a3991f8fa Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 5 Dec 2010 16:54:22 +1000 Subject: [PATCH 198/530] pkg-deps.sh: no longer filter syb since it is not in ghc7 --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 15bf088..20ba351 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -39,7 +39,7 @@ echo "}" >> pkgs.dot cp -p pkgs.dot pkgs.dot.orig # ignore library packages provided by ghc (except ghc-6.12) -GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb template-haskell time unix Win32" +GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } From b340d81569c18f3849d01eef87d13a9b43599975 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 6 Dec 2010 11:00:27 +1000 Subject: [PATCH 199/530] in pkg-deps.sh only filter ^bytestring$ --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 20ba351..5d5a83e 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -39,7 +39,7 @@ echo "}" >> pkgs.dot cp -p pkgs.dot pkgs.dot.orig # ignore library packages provided by ghc (except ghc-6.12) -GHC_PKGS="array base-4 base-3 bin-package-db bytestring Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts template-haskell time unix Win32" +GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list bytestring) Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } From 69fa88af4f6baa2737ef992f9bafcb860b6e2598 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 6 Dec 2010 11:43:22 +1000 Subject: [PATCH 200/530] hackage-status.sh: write data to a file --- hackage-status.sh | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/hackage-status.sh b/hackage-status.sh index d62fad1..dd9c870 100755 --- a/hackage-status.sh +++ b/hackage-status.sh @@ -2,13 +2,20 @@ # generates a Fedora distro package status file for hackage.haskell.org -PKGS="ghc-Boolean ghc-GLUT ghc-HTTP ghc-HUnit ghc-OpenGL ghc-QuickCheck ghc-X11 ghc-X11-xft alex ghc-attoparsec ghc-base64-bytestring ghc-binary ghc-bytestring-trie cabal-install ghc-cairo ghc-cgi ghc-chalmers-lava2000 ghc-cmdargs ghc-colour cpphs ghc-csv darcs ghc-dataenc ghc-deepseq ghc-editline ghc-feldspar-language ghc-fgl ghc-ghc-paths ghc-gio ghc-glade ghc-glib ghc-gtk gtk2hs-buildtools ghc-gtksourceview2 happy ghc-hashed-storage ghc-haskeline ghc-haskell-src ghc-haskell-src-exts ghc-hinotify hlint ghc-hslogger hscolour ghc-html ghc-libmpd ghc-mmap ghc-mtl ghc-network ghc-pango ghc-parallel ghc-parsec ghc-regex-base ghc-regex-compat ghc-regex-posix ghc-regex-tdfa ghc-split ghc-stm ghc-syb ghc-tagsoup ghc-tar ghc-terminfo ghc-text ghc-transformers ghc-type-level ghc-uniplate ghc-utf8-string ghc-xhtml xmobar xmonad ghc-xmonad-contrib ghc-zlib" +PKGS="ghc-Boolean ghc-GLUT ghc-HTTP ghc-HUnit ghc-OpenGL ghc-QuickCheck ghc-X11 ghc-X11-xft alex ghc-attoparsec ghc-base64-bytestring ghc-binary ghc-bytestring-trie cabal-install ghc-cairo ghc-cgi ghc-chalmers-lava2000 ghc-cmdargs ghc-colour cpphs ghc-csv darcs ghc-dataenc ghc-deepseq ghc-editline ghc-feldspar-language ghc-fgl ghc-ghc-paths ghc-gio ghc-glade ghc-glib ghc-gtk gtk2hs-buildtools ghc-gtksourceview2 happy ghc-hashed-storage ghc-haskeline ghc-haskell-src ghc-haskell-src-exts ghc-hinotify hlint hscolour ghc-hslogger ghc-html ghc-libmpd ghc-mmap ghc-mtl ghc-network ghc-pango ghc-parallel ghc-parsec ghc-regex-base ghc-regex-compat ghc-regex-posix ghc-regex-tdfa ghc-split ghc-stm ghc-syb ghc-tagsoup ghc-tar ghc-terminfo ghc-text ghc-transformers ghc-type-level ghc-uniplate ghc-utf8-string ghc-xhtml xmobar xmonad ghc-xmonad-contrib ghc-zlib" + +if [ -f Fedora ]; then + mv -f Fedora Fedora.previous +fi for p in $PKGS; do LATEST=$(koji latest-pkg --quiet dist-rawhide $p | cut -f1 -d' ' | sed -e "s/\(.*\)-.*/\1/") HACKAGE=$(echo $p | sed -e "s/^ghc-//") VERSION=$(echo $LATEST | sed -e "s/^$p-//") if [ -n "$VERSION" ]; then - echo "(\"$HACKAGE\",\"$VERSION\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/$p\")" + echo $HACKAGE-$VERSION + echo "(\"$HACKAGE\",\"$VERSION\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/$p\")" >> Fedora + else + echo ** No version for: $HACKAGE ** fi done From 2eee02fe7f8092b6f12684f1bdaa790e7d69c08c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 6 Dec 2010 14:34:23 +1000 Subject: [PATCH 201/530] pkg-deps.sh: exclude older syb-0.1 for ghc < 7 --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 5d5a83e..626c123 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -39,7 +39,7 @@ echo "}" >> pkgs.dot cp -p pkgs.dot pkgs.dot.orig # ignore library packages provided by ghc (except ghc-6.12) -GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list bytestring) Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts template-haskell time unix Win32" +GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list bytestring) Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb-0.1 template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } From da338d26fdaff7b982671ab614c508ca1b678587 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 8 Dec 2010 17:47:26 +1000 Subject: [PATCH 202/530] convert hackage-status.sh to hackage-fedora.py which reads package list straight from pkgdb --- hackage-fedora.py | 24 ++++++++++++++++++++++++ hackage-status.sh | 21 --------------------- 2 files changed, 24 insertions(+), 21 deletions(-) create mode 100755 hackage-fedora.py delete mode 100755 hackage-status.sh diff --git a/hackage-fedora.py b/hackage-fedora.py new file mode 100755 index 0000000..66546e4 --- /dev/null +++ b/hackage-fedora.py @@ -0,0 +1,24 @@ +#!/usr/bin/python + +# generates a Fedora distro package status file for hackage.haskell.org + +from fedora.client import PackageDB +import koji + +pkgdb = PackageDB() +p = pkgdb.user_packages('haskell-sig') + +# exclude packages not in Hackage +packages = [pkg['name'] for pkg in p.pkgs if pkg['name'] not in ['cabal2spec','emacs-haskell-mode','ghc','ghc-gtk2hs','ghc-rpm-macros','haddock','haskell-platform','hugs98']] + +session = koji.ClientSession('http://koji.fedoraproject.org/kojihub') + +for pkg in packages: + latest = session.getLatestBuilds('dist-rawhide', package=pkg) + if latest: + ver = latest[0]['version'] + name = pkg.replace('ghc-','',1) + print "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/%s\")" % (name,ver,pkg) + +# todo +## sort output diff --git a/hackage-status.sh b/hackage-status.sh deleted file mode 100755 index dd9c870..0000000 --- a/hackage-status.sh +++ /dev/null @@ -1,21 +0,0 @@ -#!/bin/sh - -# generates a Fedora distro package status file for hackage.haskell.org - -PKGS="ghc-Boolean ghc-GLUT ghc-HTTP ghc-HUnit ghc-OpenGL ghc-QuickCheck ghc-X11 ghc-X11-xft alex ghc-attoparsec ghc-base64-bytestring ghc-binary ghc-bytestring-trie cabal-install ghc-cairo ghc-cgi ghc-chalmers-lava2000 ghc-cmdargs ghc-colour cpphs ghc-csv darcs ghc-dataenc ghc-deepseq ghc-editline ghc-feldspar-language ghc-fgl ghc-ghc-paths ghc-gio ghc-glade ghc-glib ghc-gtk gtk2hs-buildtools ghc-gtksourceview2 happy ghc-hashed-storage ghc-haskeline ghc-haskell-src ghc-haskell-src-exts ghc-hinotify hlint hscolour ghc-hslogger ghc-html ghc-libmpd ghc-mmap ghc-mtl ghc-network ghc-pango ghc-parallel ghc-parsec ghc-regex-base ghc-regex-compat ghc-regex-posix ghc-regex-tdfa ghc-split ghc-stm ghc-syb ghc-tagsoup ghc-tar ghc-terminfo ghc-text ghc-transformers ghc-type-level ghc-uniplate ghc-utf8-string ghc-xhtml xmobar xmonad ghc-xmonad-contrib ghc-zlib" - -if [ -f Fedora ]; then - mv -f Fedora Fedora.previous -fi - -for p in $PKGS; do - LATEST=$(koji latest-pkg --quiet dist-rawhide $p | cut -f1 -d' ' | sed -e "s/\(.*\)-.*/\1/") - HACKAGE=$(echo $p | sed -e "s/^ghc-//") - VERSION=$(echo $LATEST | sed -e "s/^$p-//") - if [ -n "$VERSION" ]; then - echo $HACKAGE-$VERSION - echo "(\"$HACKAGE\",\"$VERSION\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/$p\")" >> Fedora - else - echo ** No version for: $HACKAGE ** - fi -done From 1f45c245965841c450dc9fa525e7f0753484ee2b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 9 Dec 2010 16:28:58 +1000 Subject: [PATCH 203/530] hackage: track f14 for now and sort the output --- hackage-fedora.py | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/hackage-fedora.py b/hackage-fedora.py index 66546e4..fca9daa 100755 --- a/hackage-fedora.py +++ b/hackage-fedora.py @@ -13,12 +13,18 @@ packages = [pkg['name'] for pkg in p.pkgs if pkg['name'] not in ['cabal2spec','e session = koji.ClientSession('http://koji.fedoraproject.org/kojihub') +outlist = [] + for pkg in packages: - latest = session.getLatestBuilds('dist-rawhide', package=pkg) + latest = session.getLatestBuilds('dist-f14-updates', package=pkg) if latest: ver = latest[0]['version'] name = pkg.replace('ghc-','',1) - print "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/%s\")" % (name,ver,pkg) + print "%s-%s" % (name,ver) + result = "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/%s\")" % (name,ver,pkg) + outlist.append(result) + +f = open('Fedora', 'w') -# todo -## sort output +for l in sorted(outlist): + f.write(l+'\n') From 37f872aa77d4369bdbdbb7b2340d879fe0371d78 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 20 Dec 2010 14:31:45 +1000 Subject: [PATCH 204/530] keep a copy of http://petersen.fedorapeople.org/hackage/Fedora file here for now --- Fedora.hackage | 68 ++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 68 insertions(+) create mode 100644 Fedora.hackage diff --git a/Fedora.hackage b/Fedora.hackage new file mode 100644 index 0000000..eb0c8d7 --- /dev/null +++ b/Fedora.hackage @@ -0,0 +1,68 @@ +("Boolean","0.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-Boolean") +("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-GLUT") +("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HTTP") +("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HUnit") +("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-OpenGL") +("QuickCheck","2.1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-QuickCheck") +("X11","1.5.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11") +("X11-xft","0.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11-xft") +("alex","2.3.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/alex") +("binary","0.5.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-binary") +("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-bytestring-trie") +("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cabal-install") +("cairo","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cairo") +("cgi","3001.1.7.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cgi") +("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-chalmers-lava2000") +("cmdargs","0.6.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cmdargs") +("colour","2.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-colour") +("cpphs","1.11",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cpphs") +("csv","0.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-csv") +("darcs","2.4.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/darcs") +("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-dataenc") +("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-deepseq") +("editline","0.2.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-editline") +("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-feldspar-language") +("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-fgl") +("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-ghc-paths") +("gio","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gio") +("glade","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-glade") +("glib","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-glib") +("gtk","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gtk") +("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/gtk2hs-buildtools") +("gtksourceview2","0.12.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gtksourceview2") +("happy","1.18.5",Just "https://admin.fedoraproject.org/pkgdb/acls/name/happy") +("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hashed-storage") +("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskeline") +("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskell-src") +("haskell-src-exts","1.9.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskell-src-exts") +("hinotify","0.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hinotify") +("hlint","1.7.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/hlint") +("hscolour","1.17",Just "https://admin.fedoraproject.org/pkgdb/acls/name/hscolour") +("hslogger","1.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hslogger") +("html","1.0.1.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-html") +("libmpd","0.4.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-libmpd") +("mmap","0.4.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mmap") +("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mtl") +("network","2.2.1.7",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-network") +("pango","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-pango") +("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-parallel") +("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-parsec") +("regex-base","0.93.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-base") +("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-compat") +("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-posix") +("regex-tdfa","1.1.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-tdfa") +("split","0.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-split") +("stm","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-stm") +("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tagsoup") +("tar","0.3.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tar") +("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-terminfo") +("text","0.8.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-text") +("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-transformers") +("type-level","0.2.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-type-level") +("uniplate","1.5.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-uniplate") +("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-utf8-string") +("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-xhtml") +("xmobar","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmobar") +("xmonad","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmonad") +("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-xmonad-contrib") +("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-zlib") From 25ba860a9ae990e08327262d861b6f8cb967d384 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 20 Dec 2010 14:32:47 +1000 Subject: [PATCH 205/530] Fedora.hackage: latest f14 stable packages --- Fedora.hackage | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/Fedora.hackage b/Fedora.hackage index eb0c8d7..d22306e 100644 --- a/Fedora.hackage +++ b/Fedora.hackage @@ -7,6 +7,8 @@ ("X11","1.5.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11") ("X11-xft","0.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11-xft") ("alex","2.3.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/alex") +("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-attoparsec") +("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-base64-bytestring") ("binary","0.5.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-binary") ("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-bytestring-trie") ("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cabal-install") @@ -50,7 +52,7 @@ ("regex-base","0.93.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-base") ("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-compat") ("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-posix") -("regex-tdfa","1.1.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-tdfa") +("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-tdfa") ("split","0.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-split") ("stm","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-stm") ("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tagsoup") From c93451f1f542b6dc01d43e50bd590b970ee29ee6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Dec 2010 11:06:23 +0900 Subject: [PATCH 206/530] move package cache file for doc cronjob to /var (#664850) Also cache long listing to notice library rebuilds. --- ghc-doc-index.cron | 22 ++++++++++++---------- ghc.spec | 9 +++++++-- 2 files changed, 19 insertions(+), 12 deletions(-) diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron index b9c5b3c..9cf2888 100755 --- a/ghc-doc-index.cron +++ b/ghc-doc-index.cron @@ -12,28 +12,30 @@ fi LOCKFILE=/var/lock/ghc-doc-index.lock # the lockfile is not meant to be perfect, it's just in case the -# two man-db cron scripts get run close to each other to keep -# them from stepping on each other's toes. The worst that will -# happen is that they will temporarily corrupt the database +# two cron scripts get run close to each other to keep +# them from stepping on each other's toes. [ -f $LOCKFILE ] && exit 0 trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT touch $LOCKFILE +PKGDIRCACHE=/var/lib/ghc/pkg-dir.cache +LISTING="env LANG=C ls -dl" + # only re-index ghc docs when there are changes cd /usr/share/doc/ghc/html/libraries -if [ -r .pkg-dir.cache ]; then - ls -d */ > .pkg-dir.cache.new - DIR_DIFF=$(diff .pkg-dir.cache .pkg-dir.cache.new) +if [ -r "$PKGDIRCACHE" ]; then + $LISTING */ > $PKGDIRCACHE.new + DIR_DIFF=$(diff $PKGDIRCACHE $PKGDIRCACHE.new) else - ls -d */ > .pkg-dir.cache + $LISTING */ > $PKGDIRCACHE fi -if [ -x "gen_contents_index" -a ! -r ".pkg-dir.cache.new" -o -n "$DIR_DIFF" ]; then +if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; then ./gen_contents_index --batch fi -if [ -f .pkg-dir.cache.new ]; then - mv -f .pkg-dir.cache{.new,} +if [ -f $PKGDIRCACHE.new ]; then + mv -f $PKGDIRCACHE{.new,} fi exit 0 diff --git a/ghc.spec b/ghc.spec index f9c4497..7134c8c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,9 +26,9 @@ %global debug_package %{nil} Name: ghc -# breaks haskell-platform-2010.2.0.0 +# haskell-platform-2011.1.0.0 Version: 7.0.1 -Release: 2%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -211,6 +211,7 @@ done %if %{with doc} mkdir -p ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly install -p --mode=755 %SOURCE3 ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly/ghc-doc-index +mkdir -p ${RPM_BUILD_ROOT}%{_localstatedir}/lib/ghc %endif %check @@ -291,6 +292,7 @@ fi %ghost %{ghcdocbasedir}/libraries/minus.gif %ghost %{ghcdocbasedir}/libraries/plus.gif %{_sysconfdir}/cron.hourly/ghc-doc-index +%{_localstatedir}/lib/ghc %endif %if %{with shared} @@ -304,6 +306,9 @@ fi %endif %changelog +* Thu Dec 30 2010 Jens Petersen - 7.0.1-3 +- store doc cronjob package cache file under /var (#664850) + * Wed Nov 24 2010 Jens Petersen - 7.0.1-2 - require libffi-devel From ed981fa029878f3c8754c72a87b94f60d7708346 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 5 Jan 2011 21:34:43 +0900 Subject: [PATCH 207/530] subpackage all the libraries with ghc-rpm-macros-0.11.1 - put rts, integer-gmp and ghc-prim in base, and ghc-binary in bin-package-db - drop the libs mega-subpackage - prof now a meta-package for backward compatibility - add devel meta-subpackage to easily install all ghc libraries - store doc cronjob package cache file under /var (#664850) - drop old extralibs bcond - no longer need to define or clean buildroot - ghc base package now requires ghc-base-devel - drop ghc-time obsoletes --- ghc.spec | 168 +++++++++++++++++++++++++++++++++---------------------- 1 file changed, 101 insertions(+), 67 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7134c8c..4563296 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ ## default enabled options ## -# experimental shared libraries support available in ghc-6.12 for x86 +# haskell shared library support available in 6.12 and later for x86 %ifarch %{ix86} x86_64 %bcond_without shared %endif @@ -17,8 +17,6 @@ %bcond_without libffi ## default disabled options ## -# include extralibs -%bcond_with extralibs # quick build profile %bcond_with quick @@ -28,6 +26,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 +# can't be reset - used by versioned library subpackages Release: 3%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: @@ -35,33 +34,26 @@ ExclusiveArch: %{ix86} x86_64 ppc alpha License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 -%if %{with extralibs} -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src-extralibs.tar.bz2 -%endif %if %{with testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 %endif Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ -BuildRoot: %{_tmppath}/%{name}-%{version}-%{release}-root-%(%{__id_u} -n) # introduced for f14 Obsoletes: ghc-doc < 6.12.3-4 Provides: ghc-doc = %{version}-%{release} # introduced for f11 Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 Obsoletes: ghc-haddock-doc < 2.4.2-3 -# introduced for f14 -Obsoletes: ghc-time-devel < 1.1.2.4-5 -Obsoletes: ghc-time-doc < 1.1.2.4-5 -BuildRequires: ghc, ghc-rpm-macros >= 0.8.2 +# introduced for f15 +Obsoletes: ghc-libs < 7.0.1-3 +BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel # for internal terminfo BuildRequires: ncurses-devel -Requires: gcc, gmp-devel, libffi-devel +Requires: gcc +Requires: ghc-base-devel # llvm is an optional dependency -%if %{with shared} -Requires: %{name}-libs = %{version}-%{release} -%endif %if %{with manual} BuildRequires: libxslt, docbook-style-xsl %endif @@ -78,7 +70,7 @@ Patch4: ghc-use-system-libffi.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimising compiler +functional programming language. It includes an optimizing compiler generating good code for a variety of platforms, together with an interactive system for convenient, quick development. The distribution includes space and time profiling facilities, a large @@ -86,35 +78,54 @@ collection of libraries, and support for various language extensions, including concurrency, exceptions, and a foreign language interface. -%if %{with shared} -%package libs -Summary: Shared libraries for GHC +%global ghc_version_override %{version} + +%ghc_binlib_package Cabal 1.10.0.0 +%ghc_binlib_package array 0.3.0.2 +%ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.0.0 +%ghc_binlib_package bin-package-db 0.0.0.0 +%ghc_binlib_package bytestring 0.9.1.8 +%ghc_binlib_package containers 0.4.0.0 +%ghc_binlib_package directory 1.1.0.0 +%ghc_binlib_package extensible-exceptions 0.1.1.2 +%ghc_binlib_package filepath 1.2.0.0 +%ghc_binlib_package ghc %{ghc_version_override} +%ghc_binlib_package haskell2010 1.0.0.0 +%ghc_binlib_package haskell98 1.1.0.0 +%ghc_binlib_package hpc 0.5.0.6 +%ghc_binlib_package old-locale 1.0.0.2 +%ghc_binlib_package old-time 1.0.0.6 +%ghc_binlib_package pretty 1.0.1.2 +%ghc_binlib_package process 1.0.1.4 +%ghc_binlib_package random 1.0.0.3 +%ghc_binlib_package template-haskell 2.5.0.0 +%ghc_binlib_package time 1.2.0.3 +%ghc_binlib_package unix 2.4.1.0 + +%global version %{ghc_version_override} + +%package devel +Summary: GHC development libraries meta package Group: Development/Libraries -Obsoletes: ghc-time < 1.1.2.4-5 +Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2,/g") -%description libs -Shared libraries for Glorious Glasgow Haskell Compilation System (GHC). -%endif +%description devel +This is a meta-package for all the development library packages in GHC. %if %{with prof} %package prof -Summary: Profiling libraries for GHC +Summary: GHC profiling libraries meta-package Group: Development/Libraries -Requires: %{name} = %{version}-%{release} +Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g") Obsoletes: ghc-haddock-prof < 2.4.2-3 -Obsoletes: ghc-time-prof < 1.1.2.4-5 %description prof -Profiling libraries for Glorious Glasgow Haskell Compilation System (GHC). +This is a meta-package for all the profiling library packages in GHC. They should be installed when GHC's profiling subsystem is needed. %endif -%global ghc_version_override %{version} - -%ghc_binlib_package -n ghc - %prep -%setup -q -n %{name}-%{version} %{?with_extralibs:-b1} %{?with_testsuite:-b2} +%setup -q -n %{name}-%{version} %{?with_testsuite:-b2} # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig # type-level too big so skip it in gen_contents_index @@ -170,32 +181,30 @@ export CFLAGS="${CFLAGS:-%optflags}" make -j$RPM_BUILD_NCPUS %install -rm -rf $RPM_BUILD_ROOT make DESTDIR=${RPM_BUILD_ROOT} install -SRC_TOP=$PWD -( cd $RPM_BUILD_ROOT - # library directories - find .%{_libdir}/%{name}-%{version} -maxdepth 1 -type d ! -name 'include' ! -name 'package.conf.d' -fprintf $SRC_TOP/rpm-lib-dir.files "%%%%dir %%p\n" - # library devel subdirs - find .%{_libdir}/%{name}-%{version} -mindepth 1 -type d \( -fprintf $SRC_TOP/rpm-dev-dir.files "%%%%dir %%p\n" \) - # split dyn, devel, conf and prof files - find .%{_libdir}/%{name}-%{version} -mindepth 1 \( -name 'libHS*-ghc%{version}.so' -fprintf $SRC_TOP/rpm-lib.files "%%%%attr(755,root,root) %%p\n" \) -o \( \( -name '*.p_hi' -o -name '*_p.a' \) -fprint $SRC_TOP/ghc-prof.files \) -o \( \( -name '*.hi' -o -name '*.dyn_hi' -o -name 'libHS*.a' -o -name 'HS*.o' -o -name '*.h' -o -name '*.conf' -o -type f -not -name 'package.cache' \) -fprint $SRC_TOP/rpm-base.files \) - # manuals (src dir are subdirs so dont duplicate them) - find .%{_docdir}/%{name}/html/* -type d ! -name libraries ! -name src > $SRC_TOP/rpm-doc-dir.files -) - -# make paths absolute (filter "./usr" to "/usr") -sed -i -e "s|\.%{_prefix}|%{_prefix}|" *.files - -cat rpm-lib-dir.files rpm-lib.files > ghc-libs.files -cat rpm-dev-dir.files rpm-base.files rpm-doc-dir.files > ghc.files - -# subpackage ghc libraries -sed -i -e "/ghc-%{version}\/ghc-%{version}/d" ghc.files ghc-libs.files ghc-prof.files -sed -i -e "/ghc-%{version}\/package.conf.d\/ghc-%{version}-.*.conf\$/d" ghc.files -sed -i -e "/html\/libraries\/ghc-%{version}\$/d" ghc.files -%ghc_gen_filelists ghc +for i in %{ghc_packages_list}; do +name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") +ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") +%ghc_gen_filelists $name $ver +done + +%ghc_gen_filelists ghc-binary 0.5.0.2 +%ghc_gen_filelists ghc-prim 0.2.0.0 +%ghc_gen_filelists integer-gmp 0.2.0.2 + +%define merge_filelist()\ +cat ghc-%1.files >> ghc-%2.files\ +cat ghc-%1-devel.files >> ghc-%2-devel.files\ +cat ghc-%1-prof.files >> ghc-%2-prof.files + +%merge_filelist integer-gmp base +%merge_filelist ghc-prim base +%merge_filelist ghc-binary bin-package-db + +ls $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.so >> ghc-base.files +ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_rts.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files +sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base{,-devel}.files # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -237,9 +246,6 @@ rm testghc/* make -C testsuite/tests/ghc-regress fast %endif -%clean -rm -rf $RPM_BUILD_ROOT - %post # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: @@ -269,15 +275,36 @@ fi %ghc_pkg_recache %ghc_reindex_haddock -%files -f ghc.files +%files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* -%dir %{_libdir}/%{name}-%{version} -%ghost %{_libdir}/%{name}-%{version}/package.conf.d/package.cache -%if %{with manual} +%dir %{ghclibdir} +%{ghclibdir}/extra-gcc-opts +%{ghclibdir}/ghc +%{ghclibdir}/ghc-asm +%{ghclibdir}/ghc-pkg +%{ghclibdir}/ghc-split +%{ghclibdir}/ghc-usage.txt +%{ghclibdir}/ghci-usage.txt +%{ghclibdir}/haddock +%{ghclibdir}/hsc2hs +%{ghclibdir}/html +%{ghclibdir}/latex +%dir %{ghclibdir}/package.conf.d +%ghost %{ghclibdir}/package.conf.d/package.cache +%{ghclibdir}/runghc +%{ghclibdir}/template-hsc.h +%{ghclibdir}/unlit %{_mandir}/man1/ghc.* +%if %{with manual} +%{ghcdocbasedir}/Cabal +%{ghcdocbasedir}/haddock +%{ghcdocbasedir}/users_guide %endif +%dir %{_docdir}/ghc +%dir %{ghcdocbasedir} +%{ghcdocbasedir}/html %if %{with doc} %dir %{ghcdocbasedir}/libraries %{ghcdocbasedir}/libraries/frames.html @@ -295,19 +322,26 @@ fi %{_localstatedir}/lib/ghc %endif -%if %{with shared} -%files libs -f ghc-libs.files +%files devel %defattr(-,root,root,-) -%endif %if %{with prof} -%files prof -f ghc-prof.files +%files prof %defattr(-,root,root,-) %endif %changelog * Thu Dec 30 2010 Jens Petersen - 7.0.1-3 +- subpackage all the libraries with ghc-rpm-macros-0.11.1 +- put rts, integer-gmp and ghc-prim in base, and ghc-binary in bin-package-db +- drop the libs mega-subpackage +- prof is now a meta-package for backward compatibility +- add devel meta-subpackage to install easily all ghc libraries - store doc cronjob package cache file under /var (#664850) +- drop old extralibs bcond +- no longer need to define or clean buildroot +- ghc base package requires ghc-base-devel +- drop ghc-time obsoletes * Wed Nov 24 2010 Jens Petersen - 7.0.1-2 - require libffi-devel From 3140ac39a12ec11f244331cec6811ad95611a22b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 5 Jan 2011 21:38:20 +0900 Subject: [PATCH 208/530] changelog tweaks --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4563296..ec4470e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -335,12 +335,12 @@ fi - subpackage all the libraries with ghc-rpm-macros-0.11.1 - put rts, integer-gmp and ghc-prim in base, and ghc-binary in bin-package-db - drop the libs mega-subpackage -- prof is now a meta-package for backward compatibility -- add devel meta-subpackage to install easily all ghc libraries +- prof now a meta-package for backward compatibility +- add devel meta-subpackage to easily install all ghc libraries - store doc cronjob package cache file under /var (#664850) - drop old extralibs bcond - no longer need to define or clean buildroot -- ghc base package requires ghc-base-devel +- ghc base package now requires ghc-base-devel - drop ghc-time obsoletes * Wed Nov 24 2010 Jens Petersen - 7.0.1-2 From 91a329e090715fbb2eec4c0e00745b7c2d296031 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 5 Jan 2011 21:48:11 +0900 Subject: [PATCH 209/530] test ghc_packages_list in requires for mock --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index ec4470e..09d7976 100644 --- a/ghc.spec +++ b/ghc.spec @@ -107,7 +107,7 @@ interface. %package devel Summary: GHC development libraries meta package Group: Development/Libraries -Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2,/g") +%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2,/g")} %description devel This is a meta-package for all the development library packages in GHC. @@ -116,7 +116,7 @@ This is a meta-package for all the development library packages in GHC. %package prof Summary: GHC profiling libraries meta-package Group: Development/Libraries -Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g") +%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g")} Obsoletes: ghc-haddock-prof < 2.4.2-3 %description prof From 67fc6891e2a8e3c79e710084f8d7ea915ff11b8b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 6 Jan 2011 15:43:34 +0900 Subject: [PATCH 210/530] fix an old changelog typo of obsolete --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 09d7976..f4d981c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -461,7 +461,7 @@ fi - add bcond for manual and extralibs - reenable ppc secondary arch - don't provide ghc-haddock-* -- remove obsoltete post requires policycoreutils +- remove obsolete post requires policycoreutils - add vanilla v to GhcLibWays when building without prof - handle without hscolour - can't smp make currently From 7dd41bb1ee051203939f03417b813f54c619dcbb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 6 Jan 2011 17:01:41 +0900 Subject: [PATCH 211/530] fix %ghc_binlib_package's appearing in srpm description --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index f4d981c..cbd5664 100644 --- a/ghc.spec +++ b/ghc.spec @@ -80,6 +80,7 @@ interface. %global ghc_version_override %{version} +%if 0%{?ghc_binlib_package:1} %ghc_binlib_package Cabal 1.10.0.0 %ghc_binlib_package array 0.3.0.2 %ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.0.0 @@ -101,6 +102,7 @@ interface. %ghc_binlib_package template-haskell 2.5.0.0 %ghc_binlib_package time 1.2.0.3 %ghc_binlib_package unix 2.4.1.0 +%endif %global version %{ghc_version_override} From f982e7ddb83dc672728ac08cd1766ab0336a1a82 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 13 Jan 2011 08:05:28 +0900 Subject: [PATCH 212/530] add BRs for various subpackaged ghc libraries needed to build ghc --- ghc.spec | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index cbd5664..927f4f5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -49,7 +49,8 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel -# for internal terminfo +BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel +# for internal terminfo BuildRequires: ncurses-devel Requires: gcc Requires: ghc-base-devel @@ -204,7 +205,9 @@ cat ghc-%1-prof.files >> ghc-%2-prof.files %merge_filelist ghc-prim base %merge_filelist ghc-binary bin-package-db +%if %{with shared} ls $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.so >> ghc-base.files +%endif ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_rts.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base{,-devel}.files @@ -333,6 +336,10 @@ fi %endif %changelog +* Thu Jan 13 2011 Jens Petersen - 7.0.1-4 +- add BRs for various subpackaged ghc libraries needed to build ghc +- condition rts .so libraries for non-shared builds + * Thu Dec 30 2010 Jens Petersen - 7.0.1-3 - subpackage all the libraries with ghc-rpm-macros-0.11.1 - put rts, integer-gmp and ghc-prim in base, and ghc-binary in bin-package-db From 63cad1510206f9155c1c2e09266a838edaf359ba Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 13 Jan 2011 10:29:27 +0900 Subject: [PATCH 213/530] fix haddock and manual filelists for no doc or no manual builds - drop build.mk assignment indents --- ghc.spec | 29 +++++++++++++++++------------ 1 file changed, 17 insertions(+), 12 deletions(-) diff --git a/ghc.spec b/ghc.spec index 927f4f5..c5c1b4f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -150,17 +150,17 @@ rm -r ghc-tarballs/libffi cat > mk/build.mk << EOF GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn} %if %{without doc} -HADDOCK_DOCS = NO +HADDOCK_DOCS = NO %endif %if %{without manual} BUILD_DOCBOOK_HTML = NO %endif %if %{with quick} -SRC_HC_OPTS = -H64m -O0 -fasm -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O0 -fasm -SplitObjs = NO +SRC_HC_OPTS = -H64m -O0 -fasm +GhcStage1HcOpts = -O -fasm +GhcStage2HcOpts = -O0 -fasm +GhcLibHcOpts = -O0 -fasm +SplitObjs = NO %endif %if %{without hscolour} HSCOLOUR_SRCS = NO @@ -292,25 +292,27 @@ fi %{ghclibdir}/ghc-split %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt -%{ghclibdir}/haddock %{ghclibdir}/hsc2hs +%if %{with doc} +%{ghclibdir}/haddock %{ghclibdir}/html %{ghclibdir}/latex +%endif %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/runghc %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit %{_mandir}/man1/ghc.* +%dir %{_docdir}/ghc +%dir %{ghcdocbasedir} +%if %{with doc} +%{ghcdocbasedir}/html %if %{with manual} %{ghcdocbasedir}/Cabal %{ghcdocbasedir}/haddock %{ghcdocbasedir}/users_guide %endif -%dir %{_docdir}/ghc -%dir %{ghcdocbasedir} -%{ghcdocbasedir}/html -%if %{with doc} %dir %{ghcdocbasedir}/libraries %{ghcdocbasedir}/libraries/frames.html %{ghcdocbasedir}/libraries/gen_contents_index @@ -336,6 +338,9 @@ fi %endif %changelog +* Thu Jan 13 2011 Jens Petersen - 7.0.1-5 +- fix no doc and no manual builds + * Thu Jan 13 2011 Jens Petersen - 7.0.1-4 - add BRs for various subpackaged ghc libraries needed to build ghc - condition rts .so libraries for non-shared builds From 4d5fcc97017917b21b161d66ab86ed954f976879 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 15 Jan 2011 22:26:35 +0900 Subject: [PATCH 214/530] add update-package.sh script to update and commit fedora hackages to latest cabal2spec --- update-package.sh | 14 ++++++++++++++ 1 file changed, 14 insertions(+) create mode 100755 update-package.sh diff --git a/update-package.sh b/update-package.sh new file mode 100755 index 0000000..1116ac2 --- /dev/null +++ b/update-package.sh @@ -0,0 +1,14 @@ +#!/bin/sh + +set -e -x + +PKG=$1 + +cd ~/fedora/haskell/$PKG/master +git pull + +cat ~/fedora/haskell/cabal2spec/master/cabal2spec-0.22.4.diff | sed -e "s/@PKG@/$PKG/" | patch -p1 + +rpmdev-bumpspec --comment="update to cabal2spec-0.22.4" $PKG.spec + +fedpkg commit -p -m "update to cabal2spec-0.22.4" From 219c6d7bba383e093bf77c1d808e51718f082cbb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 15:16:08 +1000 Subject: [PATCH 215/530] add cabal configure --enable-executable-dynamic and exclude ghc lib from lib metapackages - patch Cabal to add configure option --enable-executable-dynamic - exclude huge ghc API library from devel and prof metapackages - add a runghc test to check --- ghc.spec | 15 ++++++++++++--- update-package.sh | 2 ++ 2 files changed, 14 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index c5c1b4f..bcfc277 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -68,6 +68,9 @@ Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch Patch4: ghc-use-system-libffi.patch +# add cabal configure option --enable-executable-dynamic +# (see http://hackage.haskell.org/trac/hackage/ticket/600) +Patch5: Cabal-option-executable-dynamic.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -91,7 +94,7 @@ interface. %ghc_binlib_package directory 1.1.0.0 %ghc_binlib_package extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 -%ghc_binlib_package ghc %{ghc_version_override} +%ghc_binlib_package -x ghc %{ghc_version_override} %ghc_binlib_package haskell2010 1.0.0.0 %ghc_binlib_package haskell98 1.1.0.0 %ghc_binlib_package hpc 0.5.0.6 @@ -139,7 +142,7 @@ They should be installed when GHC's profiling subsystem is needed. %if %{with libffi} %patch4 -p1 -b .libffi %endif - +%patch5 -p1 .b .orig # use system libraries rm -r ghc-tarballs/{mingw,perl} %if %{with libffi} @@ -236,6 +239,7 @@ mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] +[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 @@ -338,6 +342,11 @@ fi %endif %changelog +* Sat Jan 22 2011 Jens Petersen - 7.0.1-6 +- patch Cabal to add configure option --enable-executable-dynamic +- exclude huge ghc API library from devel and prof metapackages +- add a runghc test to check + * Thu Jan 13 2011 Jens Petersen - 7.0.1-5 - fix no doc and no manual builds diff --git a/update-package.sh b/update-package.sh index 1116ac2..ef60175 100755 --- a/update-package.sh +++ b/update-package.sh @@ -1,5 +1,7 @@ #!/bin/sh +[ $# -ne 1 ] && echo "Usage: $(basename $0) [package]" && exit 1 + set -e -x PKG=$1 From e20b1de04440cc52b31db11964e51af7afb87314 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 15:26:49 +1000 Subject: [PATCH 216/530] add Cabal-option-executable-dynamic.patch --- Cabal-option-executable-dynamic.patch | 145 ++++++++++++++++++++++++++ 1 file changed, 145 insertions(+) create mode 100644 Cabal-option-executable-dynamic.patch diff --git a/Cabal-option-executable-dynamic.patch b/Cabal-option-executable-dynamic.patch new file mode 100644 index 0000000..4324c11 --- /dev/null +++ b/Cabal-option-executable-dynamic.patch @@ -0,0 +1,145 @@ +diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs +--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs 2011-01-22 14:49:22.000000000 +1000 ++++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs 2011-01-22 14:49:22.000000000 +1000 +@@ -488,6 +488,7 @@ + withVanillaLib = fromFlag $ configVanillaLib cfg, + withProfLib = fromFlag $ configProfLib cfg, + withSharedLib = fromFlag $ configSharedLib cfg, ++ withDynExe = fromFlag $ configDynExe cfg, + withProfExe = fromFlag $ configProfExe cfg, + withOptimization = fromFlag $ configOptimization cfg, + withGHCiLib = fromFlag $ configGHCiLib cfg, +diff -u ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs +--- ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig 2010-11-13 04:10:09.000000000 +1000 ++++ ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs 2011-01-22 14:52:52.000000000 +1000 +@@ -537,6 +537,7 @@ + info verbosity "Building C Sources..." + sequence_ [do let (odir,args) = constructCcCmdLine lbi libBi clbi pref + filename verbosity ++ False + (withProfLib lbi) + createDirectoryIfMissingVerbose verbosity True odir + runGhcProg args +@@ -671,7 +672,7 @@ + info verbosity "Building C Sources." + sequence_ [do let (odir,args) = constructCcCmdLine lbi exeBi clbi + exeDir filename verbosity +- (withProfExe lbi) ++ (withDynExe lbi) (withProfExe lbi) + createDirectoryIfMissingVerbose verbosity True odir + runGhcProg args + | filename <- cSources exeBi] +@@ -679,7 +680,7 @@ + srcMainFile <- findFile (exeDir : hsSourceDirs exeBi) modPath + + let cObjs = map (`replaceExtension` objExtension) (cSources exeBi) +- let binArgs linkExe profExe = ++ let binArgs linkExe dynExe profExe = + "--make" + : (if linkExe + then ["-o", targetDir exeNameReal] +@@ -691,6 +692,9 @@ + ++ ["-l"++lib | lib <- extraLibs exeBi] + ++ ["-L"++libDir | libDir <- extraLibDirs exeBi] + ++ concat [["-framework", f] | f <- PD.frameworks exeBi] ++ ++ if dynExe ++ then ["-dynamic"] ++ else [] + ++ if profExe + then ["-prof", + "-hisuf", "p_hi", +@@ -704,9 +708,9 @@ + -- run at compile time needs to be the vanilla ABI so it can + -- be loaded up and run by the compiler. + when (withProfExe lbi && TemplateHaskell `elem` allExtensions exeBi) +- (runGhcProg (binArgs False False)) ++ (runGhcProg (binArgs (withDynExe lbi) False False)) + +- runGhcProg (binArgs True (withProfExe lbi)) ++ runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi)) + + -- | Filter the "-threaded" flag when profiling as it does not + -- work with ghc-6.8 and older. +@@ -836,9 +840,9 @@ + ierror = error ("internal error: unexpected package db stack: " ++ show dbstack) + + constructCcCmdLine :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo +- -> FilePath -> FilePath -> Verbosity -> Bool ++ -> FilePath -> FilePath -> Verbosity -> Bool -> Bool + ->(FilePath,[String]) +-constructCcCmdLine lbi bi clbi pref filename verbosity profiling ++constructCcCmdLine lbi bi clbi pref filename verbosity dynamic profiling + = let odir | compilerVersion (compiler lbi) >= Version [6,4,1] [] = pref + | otherwise = pref takeDirectory filename + -- ghc 6.4.1 fixed a bug in -odir handling +@@ -852,6 +856,7 @@ + -- option to ghc here when compiling C code, so that the PROFILING + -- macro gets defined. The macro is used in ghc's Rts.h in the + -- definitions of closure layouts (Closures.h). ++ ++ ["-dynamic" | dynamic] + ++ ["-prof" | profiling]) + + ghcCcOptions :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo +diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs +--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs 2011-01-22 14:49:22.000000000 +1000 ++++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs 2011-01-22 14:49:22.000000000 +1000 +@@ -118,6 +118,7 @@ + withVanillaLib:: Bool, -- ^Whether to build normal libs. + withProfLib :: Bool, -- ^Whether to build profiling versions of libs. + withSharedLib :: Bool, -- ^Whether to build shared versions of libs. ++ withDynExe :: Bool, -- ^Whether to link executables dynamically + withProfExe :: Bool, -- ^Whether to build executables for profiling. + withOptimization :: OptimisationLevel, -- ^Whether to build with optimization (if available). + withGHCiLib :: Bool, -- ^Whether to build libs suitable for use with GHCi. +diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs +--- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs 2011-01-22 14:49:22.000000000 +1000 ++++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs 2011-01-22 14:49:22.000000000 +1000 +@@ -270,6 +270,7 @@ + configVanillaLib :: Flag Bool, -- ^Enable vanilla library + configProfLib :: Flag Bool, -- ^Enable profiling in the library + configSharedLib :: Flag Bool, -- ^Build shared library ++ configDynExe :: Flag Bool, -- ^Enable dynamic linking of the executables. + configProfExe :: Flag Bool, -- ^Enable profiling in the executables. + configConfigureArgs :: [String], -- ^Extra arguments to @configure@ + configOptimization :: Flag OptimisationLevel, -- ^Enable optimization. +@@ -301,6 +302,7 @@ + configVanillaLib = Flag True, + configProfLib = Flag False, + configSharedLib = Flag False, ++ configDynExe = Flag False, + configProfExe = Flag False, + configOptimization = Flag NormalOptimisation, + configProgPrefix = Flag (toPathTemplate ""), +@@ -388,10 +390,16 @@ + configSharedLib (\v flags -> flags { configSharedLib = v }) + (boolOpt [] []) + ++ ,option "" ["executable-dynamic"] ++ "Executable dynamic linking (fedora patch)" ++ configDynExe (\v flags -> flags { configDynExe = v }) ++ (boolOpt [] []) ++ + ,option "" ["executable-profiling"] + "Executable profiling" + configProfExe (\v flags -> flags { configProfExe = v }) + (boolOpt [] []) ++ + ,multiOption "optimization" + configOptimization (\v flags -> flags { configOptimization = v }) + [optArg' "n" (Flag . flagToOptimisationLevel) +@@ -553,6 +561,7 @@ + configVanillaLib = mempty, + configProfLib = mempty, + configSharedLib = mempty, ++ configDynExe = mempty, + configProfExe = mempty, + configConfigureArgs = mempty, + configOptimization = mempty, +@@ -583,6 +592,7 @@ + configVanillaLib = combine configVanillaLib, + configProfLib = combine configProfLib, + configSharedLib = combine configSharedLib, ++ configDynExe = combine configDynExe, + configProfExe = combine configProfExe, + configConfigureArgs = combine configConfigureArgs, + configOptimization = combine configOptimization, From 8c1f0be4def81faa1fba93acbf94363ff3f77bb6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 15:30:08 +1000 Subject: [PATCH 217/530] fix the Cabal %patch line --- ghc.spec | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index bcfc277..5a90df0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -138,17 +138,17 @@ They should be installed when GHC's profiling subsystem is needed. %patch2 -p1 # disable gen_contents_index when not --batch for cron %patch3 -p1 -# use system libffi -%if %{with libffi} -%patch4 -p1 -b .libffi -%endif -%patch5 -p1 .b .orig + # use system libraries rm -r ghc-tarballs/{mingw,perl} +# use system libffi %if %{with libffi} +%patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi %endif +%patch5 -p1 -b .orig + %build cat > mk/build.mk << EOF GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn} From e122c83335d4ca2e15b09a921d957c5331cf07c7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 18:10:46 +1000 Subject: [PATCH 218/530] condition ghc_binlib_packages on new ghclibdir instead of ghc_version --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5a90df0..d9193a7 100644 --- a/ghc.spec +++ b/ghc.spec @@ -84,7 +84,7 @@ interface. %global ghc_version_override %{version} -%if 0%{?ghc_binlib_package:1} +%if 0%{?ghclibdir:1} %ghc_binlib_package Cabal 1.10.0.0 %ghc_binlib_package array 0.3.0.2 %ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.0.0 From 35a3ed6600c14eba29dcc7503ccf2c3e413f6a69 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 20:09:14 +1000 Subject: [PATCH 219/530] comment out the new inplace runghc test in %check since it doesn't work --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index d9193a7..b92e18a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -239,7 +239,8 @@ mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] -[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] +# don't seem to work inplace: +#[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 @@ -345,7 +346,6 @@ fi * Sat Jan 22 2011 Jens Petersen - 7.0.1-6 - patch Cabal to add configure option --enable-executable-dynamic - exclude huge ghc API library from devel and prof metapackages -- add a runghc test to check * Thu Jan 13 2011 Jens Petersen - 7.0.1-5 - fix no doc and no manual builds From b01bee35adb765b624ceb6898e2d4c6e07508ccc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 21:02:26 +1000 Subject: [PATCH 220/530] need to generate filelist for ghc-ghc --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index b92e18a..880fbf7 100644 --- a/ghc.spec +++ b/ghc.spec @@ -196,6 +196,7 @@ ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") done %ghc_gen_filelists ghc-binary 0.5.0.2 +%ghc_gen_filelists ghc-ghc %{ghc_version_override} %ghc_gen_filelists ghc-prim 0.2.0.0 %ghc_gen_filelists integer-gmp 0.2.0.2 From 823fc8d38679c266465d5587522a2c4e4ffaba72 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 22 Jan 2011 21:49:39 +1000 Subject: [PATCH 221/530] the ghc API lib pkgname is ghc not ghc-ghc --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 880fbf7..6a1a619 100644 --- a/ghc.spec +++ b/ghc.spec @@ -195,8 +195,8 @@ ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver done +%ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghc-binary 0.5.0.2 -%ghc_gen_filelists ghc-ghc %{ghc_version_override} %ghc_gen_filelists ghc-prim 0.2.0.0 %ghc_gen_filelists integer-gmp 0.2.0.2 From cb88bd799a33848555723ddfae22b9c40801979d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 29 Jan 2011 20:50:36 +1000 Subject: [PATCH 222/530] save latest F14 packages --- Fedora.hackage => hackage/Fedora | 10 ++++++++-- hackage-fedora.py => hackage/hackage-fedora.py | 0 2 files changed, 8 insertions(+), 2 deletions(-) rename Fedora.hackage => hackage/Fedora (89%) rename hackage-fedora.py => hackage/hackage-fedora.py (100%) diff --git a/Fedora.hackage b/hackage/Fedora similarity index 89% rename from Fedora.hackage rename to hackage/Fedora index d22306e..45e3431 100644 --- a/Fedora.hackage +++ b/hackage/Fedora @@ -2,6 +2,7 @@ ("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-GLUT") ("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HTTP") ("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HUnit") +("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-MissingH") ("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-OpenGL") ("QuickCheck","2.1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-QuickCheck") ("X11","1.5.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11") @@ -15,14 +16,17 @@ ("cairo","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cairo") ("cgi","3001.1.7.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cgi") ("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-chalmers-lava2000") -("cmdargs","0.6.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cmdargs") +("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cmdargs") ("colour","2.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-colour") ("cpphs","1.11",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cpphs") ("csv","0.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-csv") ("darcs","2.4.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/darcs") ("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-dataenc") ("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-deepseq") +("digest","0.0.0.8",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-digest") ("editline","0.2.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-editline") +("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-enumerator") +("failure","0.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-failure") ("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-feldspar-language") ("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-fgl") ("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-ghc-paths") @@ -45,6 +49,7 @@ ("libmpd","0.4.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-libmpd") ("mmap","0.4.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mmap") ("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mtl") +("neither","0.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-neither") ("network","2.2.1.7",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-network") ("pango","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-pango") ("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-parallel") @@ -58,7 +63,7 @@ ("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tagsoup") ("tar","0.3.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tar") ("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-terminfo") -("text","0.8.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-text") +("text","0.10.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-text") ("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-transformers") ("type-level","0.2.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-type-level") ("uniplate","1.5.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-uniplate") @@ -67,4 +72,5 @@ ("xmobar","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmobar") ("xmonad","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmonad") ("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-xmonad-contrib") +("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-zip-archive") ("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-zlib") diff --git a/hackage-fedora.py b/hackage/hackage-fedora.py similarity index 100% rename from hackage-fedora.py rename to hackage/hackage-fedora.py From b9101c878d01f9221e87d05b030b47a1b7f0f89b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 29 Jan 2011 20:51:26 +1000 Subject: [PATCH 223/530] update hackage package url to use community pages --- hackage/hackage-fedora.py | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/hackage/hackage-fedora.py b/hackage/hackage-fedora.py index fca9daa..1f21ef6 100755 --- a/hackage/hackage-fedora.py +++ b/hackage/hackage-fedora.py @@ -9,7 +9,7 @@ pkgdb = PackageDB() p = pkgdb.user_packages('haskell-sig') # exclude packages not in Hackage -packages = [pkg['name'] for pkg in p.pkgs if pkg['name'] not in ['cabal2spec','emacs-haskell-mode','ghc','ghc-gtk2hs','ghc-rpm-macros','haddock','haskell-platform','hugs98']] +packages = [pkg['name'] for pkg in p.pkgs if pkg['name'] not in ['cabal2spec','emacs-haskell-mode','ghc','ghc-gtk2hs','ghc-rpm-macros','haskell-platform','hugs98']] session = koji.ClientSession('http://koji.fedoraproject.org/kojihub') @@ -21,7 +21,7 @@ for pkg in packages: ver = latest[0]['version'] name = pkg.replace('ghc-','',1) print "%s-%s" % (name,ver) - result = "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/pkgdb/acls/name/%s\")" % (name,ver,pkg) + result = "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/community/?package=%s#package_maintenance\")" % (name,ver,pkg) outlist.append(result) f = open('Fedora', 'w') From de9d772c9c3c06ab1a5cd036b88f15ce1f8c6499 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 29 Jan 2011 20:51:59 +1000 Subject: [PATCH 224/530] include LICENSE files in the shared lib subpackages --- ghc.spec | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 6a1a619..af2195e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -193,6 +193,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver +echo "%doc libraries/$name/LICENSE" >> ghc-$name.files done %ghc_gen_filelists ghc %{ghc_version_override} @@ -203,7 +204,9 @@ done %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ -cat ghc-%1-prof.files >> ghc-%2-prof.files +cat ghc-%1-prof.files >> ghc-%2-prof.files\ +cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ +echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base @@ -344,6 +347,9 @@ fi %endif %changelog +* Mon Jan 24 2011 Jens Petersen +- include LICENSE files in the shared lib subpackages + * Sat Jan 22 2011 Jens Petersen - 7.0.1-6 - patch Cabal to add configure option --enable-executable-dynamic - exclude huge ghc API library from devel and prof metapackages From e486d4f8b653db9d49aa6d922e51044210ca0d42 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 29 Jan 2011 20:56:01 +1000 Subject: [PATCH 225/530] update hackage url to community --- hackage/Fedora | 152 ++++++++++++++++++++++++------------------------- 1 file changed, 76 insertions(+), 76 deletions(-) diff --git a/hackage/Fedora b/hackage/Fedora index 45e3431..5b126ce 100644 --- a/hackage/Fedora +++ b/hackage/Fedora @@ -1,76 +1,76 @@ -("Boolean","0.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-Boolean") -("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-GLUT") -("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HTTP") -("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-HUnit") -("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-MissingH") -("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-OpenGL") -("QuickCheck","2.1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-QuickCheck") -("X11","1.5.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11") -("X11-xft","0.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-X11-xft") -("alex","2.3.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/alex") -("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-attoparsec") -("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-base64-bytestring") -("binary","0.5.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-binary") -("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-bytestring-trie") -("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cabal-install") -("cairo","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cairo") -("cgi","3001.1.7.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cgi") -("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-chalmers-lava2000") -("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-cmdargs") -("colour","2.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-colour") -("cpphs","1.11",Just "https://admin.fedoraproject.org/pkgdb/acls/name/cpphs") -("csv","0.1.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-csv") -("darcs","2.4.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/darcs") -("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-dataenc") -("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-deepseq") -("digest","0.0.0.8",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-digest") -("editline","0.2.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-editline") -("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-enumerator") -("failure","0.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-failure") -("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-feldspar-language") -("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-fgl") -("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-ghc-paths") -("gio","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gio") -("glade","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-glade") -("glib","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-glib") -("gtk","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gtk") -("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/gtk2hs-buildtools") -("gtksourceview2","0.12.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-gtksourceview2") -("happy","1.18.5",Just "https://admin.fedoraproject.org/pkgdb/acls/name/happy") -("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hashed-storage") -("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskeline") -("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskell-src") -("haskell-src-exts","1.9.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-haskell-src-exts") -("hinotify","0.3.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hinotify") -("hlint","1.7.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/hlint") -("hscolour","1.17",Just "https://admin.fedoraproject.org/pkgdb/acls/name/hscolour") -("hslogger","1.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-hslogger") -("html","1.0.1.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-html") -("libmpd","0.4.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-libmpd") -("mmap","0.4.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mmap") -("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-mtl") -("neither","0.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-neither") -("network","2.2.1.7",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-network") -("pango","0.11.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-pango") -("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-parallel") -("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-parsec") -("regex-base","0.93.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-base") -("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-compat") -("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-posix") -("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-regex-tdfa") -("split","0.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-split") -("stm","2.1.2.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-stm") -("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tagsoup") -("tar","0.3.1.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-tar") -("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-terminfo") -("text","0.10.0.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-text") -("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-transformers") -("type-level","0.2.4",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-type-level") -("uniplate","1.5.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-uniplate") -("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-utf8-string") -("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-xhtml") -("xmobar","0.11.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmobar") -("xmonad","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/xmonad") -("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-xmonad-contrib") -("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-zip-archive") -("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/pkgdb/acls/name/ghc-zlib") +("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") +("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") +("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") +("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") +("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") +("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") +("QuickCheck","2.1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") +("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") +("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") +("alex","2.3.3",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") +("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") +("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") +("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") +("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") +("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") +("cairo","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-cairo#package_maintenance") +("cgi","3001.1.7.3",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") +("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") +("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") +("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") +("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") +("csv","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") +("darcs","2.4.4",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") +("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") +("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") +("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") +("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") +("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") +("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") +("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") +("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") +("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") +("gio","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-gio#package_maintenance") +("glade","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-glade#package_maintenance") +("glib","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-glib#package_maintenance") +("gtk","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-gtk#package_maintenance") +("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") +("gtksourceview2","0.12.1",Just "https://admin.fedoraproject.org/community/?package=ghc-gtksourceview2#package_maintenance") +("happy","1.18.5",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") +("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") +("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") +("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") +("haskell-src-exts","1.9.0",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") +("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") +("hlint","1.7.3",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") +("hscolour","1.17",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") +("hslogger","1.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") +("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") +("libmpd","0.4.2",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") +("mmap","0.4.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") +("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") +("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") +("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") +("pango","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") +("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") +("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") +("regex-base","0.93.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") +("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") +("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") +("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") +("split","0.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") +("stm","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") +("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") +("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") +("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") +("text","0.10.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") +("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") +("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") +("uniplate","1.5.1",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") +("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") +("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") +("xmobar","0.11.1",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") +("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") +("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") +("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") +("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") From 11783989664c10e8589df6ad51381b597e41d08b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 31 Jan 2011 15:17:56 +1000 Subject: [PATCH 226/530] tweak shared lib comment for x86 --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index af2195e..7379b85 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ ## default enabled options ## -# haskell shared library support available in 6.12 and later for x86 +# haskell shared library support available in 6.12 and later for x86* %ifarch %{ix86} x86_64 %bcond_without shared %endif @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 6%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -347,7 +347,7 @@ fi %endif %changelog -* Mon Jan 24 2011 Jens Petersen +* Mon Jan 31 2011 Jens Petersen - 7.0.1-7 - include LICENSE files in the shared lib subpackages * Sat Jan 22 2011 Jens Petersen - 7.0.1-6 From 2b3b4ca01a5fd771e2d29e076d3bea2116360c50 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 Feb 2011 16:43:17 +1000 Subject: [PATCH 227/530] add hackage/Makefile --- hackage/Makefile | 5 +++++ 1 file changed, 5 insertions(+) create mode 100644 hackage/Makefile diff --git a/hackage/Makefile b/hackage/Makefile new file mode 100644 index 0000000..13cabb5 --- /dev/null +++ b/hackage/Makefile @@ -0,0 +1,5 @@ +all: + ./hackage-fedora.py + +push: + scp Fedora fedorapeople.org:public_html/hackage/ From 2ab657490d53c9793cf8b28bc0f07c37edd243fb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 Feb 2011 16:44:28 +1000 Subject: [PATCH 228/530] add hedgewars-server and wiki url to pkg-deps.sh --- pkg-deps.sh | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 626c123..af887f9 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -14,7 +14,7 @@ ghc-pkg dot --global | sed '$d' > pkgs.dot # check for binary deps too # (exclude binlib for now since covered by libs): cpphs, darcs, hlint, hscolour, xmonad -for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform xmobar; do +for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform hedgewars-server xmobar; do PKG_THERE=yes PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing $i" ; } if [ "$PKG_THERE" = "yes" ]; then @@ -50,3 +50,5 @@ if [ -n "$DISPLAY" ]; then else echo open ".pkg-deps/pkgs.svg" to display pkg graph fi + +echo https://fedoraproject.org/wiki/Haskell_package_interdependencies From 0eb21ddf53b7febf56154e085b30e4606921593b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 8 Feb 2011 11:18:03 +1000 Subject: [PATCH 229/530] hackage: add ansi-terminal, attempt, blaze-builder, bytestring-nums, haddock, mtlparse, process-leksah, safe, xml, zlib-bindings --- hackage/Fedora | 10 ++++++++++ 1 file changed, 10 insertions(+) diff --git a/hackage/Fedora b/hackage/Fedora index 5b126ce..78cfa7c 100644 --- a/hackage/Fedora +++ b/hackage/Fedora @@ -8,9 +8,13 @@ ("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") ("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") ("alex","2.3.3",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") +("ansi-terminal","0.5.5",Just "https://admin.fedoraproject.org/community/?package=ghc-ansi-terminal#package_maintenance") +("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") ("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") ("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") ("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") +("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") +("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") ("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") ("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") ("cairo","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-cairo#package_maintenance") @@ -36,6 +40,7 @@ ("gtk","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-gtk#package_maintenance") ("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") ("gtksourceview2","0.12.1",Just "https://admin.fedoraproject.org/community/?package=ghc-gtksourceview2#package_maintenance") +("haddock","2.4.2",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") ("happy","1.18.5",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") ("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") ("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") @@ -49,15 +54,18 @@ ("libmpd","0.4.2",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") ("mmap","0.4.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") ("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") +("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") ("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") ("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") ("pango","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") ("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") ("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") +("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") ("regex-base","0.93.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") ("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") ("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") ("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") +("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") ("split","0.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") ("stm","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") ("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") @@ -69,8 +77,10 @@ ("uniplate","1.5.1",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") ("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") ("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") +("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") ("xmobar","0.11.1",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") ("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") ("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") ("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") ("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") +("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") From 122ef38c5a3a330494e5cf89ceb4f270c279ef13 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 8 Feb 2011 11:19:10 +1000 Subject: [PATCH 230/530] add a colon to pkgdeps.sh missing pkg output --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index af887f9..1bcb6ee 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -16,7 +16,7 @@ ghc-pkg dot --global | sed '$d' > pkgs.dot # (exclude binlib for now since covered by libs): cpphs, darcs, hlint, hscolour, xmonad for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform hedgewars-server xmobar; do PKG_THERE=yes - PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing $i" ; } + PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing: $i" ; } if [ "$PKG_THERE" = "yes" ]; then echo \"$PKG\" >> pkgs.dot case $i in From b68147ffa3eef40393fb7ea1b0f39b5f00a51533 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 9 Feb 2011 13:08:25 +1000 Subject: [PATCH 231/530] add pandoc and texmath --- hackage/{Fedora => f14} | 2 ++ 1 file changed, 2 insertions(+) rename hackage/{Fedora => f14} (97%) diff --git a/hackage/Fedora b/hackage/f14 similarity index 97% rename from hackage/Fedora rename to hackage/f14 index 78cfa7c..aacba4e 100644 --- a/hackage/Fedora +++ b/hackage/f14 @@ -57,6 +57,7 @@ ("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") ("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") ("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") +("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") ("pango","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") ("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") ("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") @@ -71,6 +72,7 @@ ("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") ("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") ("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") +("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") ("text","0.10.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") ("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") ("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") From 1ca19b8b84b8bfc4ad6bf7af92f1e7433375ef26 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 9 Feb 2011 13:19:18 +1000 Subject: [PATCH 232/530] add hackage data for f13 --- hackage/f13 | 80 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 80 insertions(+) create mode 100644 hackage/f13 diff --git a/hackage/f13 b/hackage/f13 new file mode 100644 index 0000000..25445ee --- /dev/null +++ b/hackage/f13 @@ -0,0 +1,80 @@ +("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") +("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") +("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") +("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") +("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") +("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") +("QuickCheck","2.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") +("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") +("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") +("alex","2.3.2",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") +("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") +("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") +("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") +("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") +("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") +("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") +("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") +("cabal-install","0.8.0",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") +("cgi","3001.1.7.2",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") +("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") +("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") +("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") +("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") +("csv","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") +("darcs","2.4.4",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") +("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") +("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") +("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") +("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") +("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") +("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") +("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") +("fgl","5.4.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") +("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") +("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") +("haddock","2.4.2",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") +("happy","1.18.4",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") +("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") +("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") +("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") +("haskell-src-exts","1.8.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") +("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") +("hlint","1.6.20",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") +("hscolour","1.16",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") +("hslogger","1.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") +("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") +("libmpd","0.4.2",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") +("mmap","0.4.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") +("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") +("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") +("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") +("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") +("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") +("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") +("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") +("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") +("regex-base","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") +("regex-compat","0.92",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") +("regex-posix","0.94.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") +("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") +("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") +("split","0.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") +("stm","2.1.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") +("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") +("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") +("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") +("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") +("text","0.10.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") +("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") +("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") +("uniplate","1.5.1",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") +("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") +("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") +("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") +("xmobar","0.11.1",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") +("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") +("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") +("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") +("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") +("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") From 6df1300262af533fa9f6d5074e784f9e26891270 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 9 Feb 2011 13:25:11 +1000 Subject: [PATCH 233/530] add hackage data for f15 --- hackage/f15 | 91 +++++++++++++++++++++++++++++++++++++++++++++++++++++ 1 file changed, 91 insertions(+) create mode 100644 hackage/f15 diff --git a/hackage/f15 b/hackage/f15 new file mode 100644 index 0000000..8c72490 --- /dev/null +++ b/hackage/f15 @@ -0,0 +1,91 @@ +("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") +("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") +("HTTP","4000.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") +("HUnit","1.2.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") +("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") +("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") +("QuickCheck","2.4.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") +("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") +("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") +("alex","2.3.4",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") +("ansi-terminal","0.5.5",Just "https://admin.fedoraproject.org/community/?package=ghc-ansi-terminal#package_maintenance") +("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") +("attoparsec","0.8.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") +("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") +("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") +("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") +("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") +("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") +("cabal-install","0.9.5",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") +("cairo","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-cairo#package_maintenance") +("cgi","3001.1.7.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") +("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") +("cmdargs","0.6.7",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") +("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") +("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") +("csv","0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") +("darcs","2.5",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") +("dataenc","0.13.0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") +("deepseq","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") +("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") +("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") +("enumerator","0.4.5",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") +("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") +("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") +("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") +("ghc-paths","0.1.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") +("gio","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-gio#package_maintenance") +("glade","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-glade#package_maintenance") +("glib","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-glib#package_maintenance") +("gtk","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-gtk#package_maintenance") +("gtk2hs-buildtools","0.12.0",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") +("gtksourceview2","0.12.2",Just "https://admin.fedoraproject.org/community/?package=ghc-gtksourceview2#package_maintenance") +("haddock","2.9.1",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") +("hamlet","0.6.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-hamlet#package_maintenance") +("happy","1.18.6",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") +("hashed-storage","0.5.4",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") +("haskeline","0.6.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") +("haskell-src","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") +("haskell-src-exts","1.9.6",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") +("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") +("hlint","1.8.3",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") +("hscolour","1.17",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") +("hslogger","1.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") +("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") +("libmpd","0.5.0",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") +("mmap","0.5.7",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") +("mtl","2.0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") +("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") +("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") +("network","2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") +("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") +("pango","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") +("parallel","3.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") +("parsec","3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") +("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") +("regex-base","0.93.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") +("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") +("regex-posix","0.94.4",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") +("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") +("regexpr","0.5.3",Just "https://admin.fedoraproject.org/community/?package=ghc-regexpr#package_maintenance") +("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") +("split","0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") +("stm","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") +("syb","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-syb#package_maintenance") +("tagsoup","0.12",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") +("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") +("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") +("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") +("text","0.11.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") +("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") +("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") +("uniplate","1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") +("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") +("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") +("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") +("xmobar","0.12",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") +("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") +("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") +("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") +("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") +("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") From 127c62537065c5ead7984cf5f628a7156fb2850d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 9 Feb 2011 13:26:33 +1000 Subject: [PATCH 234/530] add a fedora release arg to hackage.py and save to release file --- hackage/Makefile | 6 ++++-- hackage/hackage-fedora.py | 11 +++++++++-- 2 files changed, 13 insertions(+), 4 deletions(-) diff --git a/hackage/Makefile b/hackage/Makefile index 13cabb5..6837520 100644 --- a/hackage/Makefile +++ b/hackage/Makefile @@ -1,5 +1,7 @@ +CURRENT = f14 + all: - ./hackage-fedora.py + ./hackage-fedora.py $(CURRENT) push: - scp Fedora fedorapeople.org:public_html/hackage/ + scp $(CURRENT) fedorapeople.org:public_html/hackage/Fedora diff --git a/hackage/hackage-fedora.py b/hackage/hackage-fedora.py index 1f21ef6..3ed9d14 100755 --- a/hackage/hackage-fedora.py +++ b/hackage/hackage-fedora.py @@ -4,6 +4,13 @@ from fedora.client import PackageDB import koji +import sys + +if len(sys.argv) > 1: + release = sys.argv[1] +else: + release = 'f14' + print release + ':' pkgdb = PackageDB() p = pkgdb.user_packages('haskell-sig') @@ -16,7 +23,7 @@ session = koji.ClientSession('http://koji.fedoraproject.org/kojihub') outlist = [] for pkg in packages: - latest = session.getLatestBuilds('dist-f14-updates', package=pkg) + latest = session.getLatestBuilds('dist-' + release + '-updates', package=pkg) if latest: ver = latest[0]['version'] name = pkg.replace('ghc-','',1) @@ -24,7 +31,7 @@ for pkg in packages: result = "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/community/?package=%s#package_maintenance\")" % (name,ver,pkg) outlist.append(result) -f = open('Fedora', 'w') +f = open(release, 'w') for l in sorted(outlist): f.write(l+'\n') From c8638ad65ca956fcee76c48e18ce24ebdff6cce5 Mon Sep 17 00:00:00 2001 From: Dennis Gilmore Date: Tue, 8 Feb 2011 18:52:26 -0600 Subject: [PATCH 235/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 7379b85..c1f0408 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -347,6 +347,9 @@ fi %endif %changelog +* Tue Feb 08 2011 Fedora Release Engineering - 7.0.1-8 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild + * Mon Jan 31 2011 Jens Petersen - 7.0.1-7 - include LICENSE files in the shared lib subpackages From ebb79e2ae95ececd29e57a7600de3e4bfd45dd81 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 9 Feb 2011 18:31:32 +1000 Subject: [PATCH 236/530] filter singleton packages from pkg-deps.sh --- pkg-deps.sh | 3 +++ 1 file changed, 3 insertions(+) diff --git a/pkg-deps.sh b/pkg-deps.sh index 1bcb6ee..5387c43 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -42,6 +42,9 @@ cp -p pkgs.dot pkgs.dot.orig GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list bytestring) Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb-0.1 template-haskell time unix Win32" for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done +# remove singletons +sed -i -e /^"[^ ]*"$/d pkgs.dot + which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg From af406c52e9e67851b8aad08837b364cb9b1bacfb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 11:41:10 +1000 Subject: [PATCH 237/530] fix non shared build for ppc, etc --- ghc.spec | 20 ++++++++++++-------- 1 file changed, 12 insertions(+), 8 deletions(-) diff --git a/ghc.spec b/ghc.spec index c1f0408..c5214cf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,7 +1,7 @@ ## default enabled options ## # haskell shared library support available in 6.12 and later for x86* -%ifarch %{ix86} x86_64 -%bcond_without shared +%ifnarch %{ix86} x86_64 +%global without_shared 1 %endif %bcond_without doc # test builds can made faster and smaller by disabling profiled libraries @@ -27,7 +27,7 @@ Name: ghc # haskell-platform-2011.1.0.0 Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -151,7 +151,7 @@ rm -r ghc-tarballs/libffi %build cat > mk/build.mk << EOF -GhcLibWays = v %{?with_prof:p} %{?with_shared:dyn} +GhcLibWays = v %{?with_prof:p} %{!?without_shared:dyn} %if %{without doc} HADDOCK_DOCS = NO %endif @@ -179,7 +179,7 @@ export CFLAGS="${CFLAGS:-%optflags}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - %{?with_shared:--enable-shared} + %{!?without_shared:--enable-shared} # 4 cpus or more sometimes breaks build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) @@ -212,11 +212,12 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist ghc-prim base %merge_filelist ghc-binary bin-package-db -%if %{with shared} +%if 0%{!?without_shared:1} ls $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.so >> ghc-base.files +sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_rts.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files -sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base{,-devel}.files +sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -250,7 +251,7 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if %{with shared} +%if 0%{!?without_shared:1} echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] @@ -347,6 +348,9 @@ fi %endif %changelog +* Thu Feb 10 2011 Jens Petersen - 7.0.1-9 +- fix non shared build for ppc + * Tue Feb 08 2011 Fedora Release Engineering - 7.0.1-8 - Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild From 4a73d7ade2914f535d2d424dba4f62ce2e13b943 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 12:58:13 +1000 Subject: [PATCH 238/530] more non shared filelist fixes --- ghc.spec | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index c5214cf..88d6a77 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ ## default enabled options ## -# haskell shared library support available in 6.12 and later for x86* +# haskell shared library support available from 6.12 for x86* %ifnarch %{ix86} x86_64 %global without_shared 1 %endif @@ -25,6 +25,7 @@ Name: ghc # haskell-platform-2011.1.0.0 +# NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.1 # can't be reset - used by versioned library subpackages Release: 9%{?dist} @@ -193,7 +194,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name.files +echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?without_shared:-devel}.files done %ghc_gen_filelists ghc %{ghc_version_override} @@ -202,7 +203,9 @@ done %ghc_gen_filelists integer-gmp 0.2.0.2 %define merge_filelist()\ +%if 0%{!?without_shared:1}\ cat ghc-%1.files >> ghc-%2.files\ +%endif\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cat ghc-%1-prof.files >> ghc-%2-prof.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ @@ -213,10 +216,10 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist ghc-binary bin-package-db %if 0%{!?without_shared:1} -ls $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.so >> ghc-base.files +ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif -ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHSrts*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_rts.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files +ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files # these are handled as alternatives @@ -349,7 +352,7 @@ fi %changelog * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 -- fix non shared build for ppc +- fix non shared build for ppc, etc * Tue Feb 08 2011 Fedora Release Engineering - 7.0.1-8 - Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild From 3e757b566087e65386d66a8c43f55f1a07e3a907 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 14:10:31 +1000 Subject: [PATCH 239/530] disable system libffi and ghc-*-devel BRs for secondary archs --- ghc.spec | 6 ++++++ 1 file changed, 6 insertions(+) diff --git a/ghc.spec b/ghc.spec index 88d6a77..00787a4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,7 +14,9 @@ # include colored html src %bcond_without hscolour # use system libffi +%ifarch %{ix86} x86_64 %bcond_without libffi +%endif ## default disabled options ## # quick build profile @@ -50,7 +52,9 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel +%ifarch %{ix86} x86_64 BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel +%endif # for internal terminfo BuildRequires: ncurses-devel Requires: gcc @@ -353,6 +357,8 @@ fi %changelog * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 - fix non shared build for ppc, etc +- disable system libffi for secondary archs +- temporarily disable ghc-*-devel BRs for ppc * Tue Feb 08 2011 Fedora Release Engineering - 7.0.1-8 - Rebuilt for https://fedoraproject.org/wiki/Fedora_15_Mass_Rebuild From 1534a11b27fa02388e1b8f8e9a4cf690a8920089 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 16:15:17 +1000 Subject: [PATCH 240/530] handle HSffi.o for without_shared --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 00787a4..d4d6b48 100644 --- a/ghc.spec +++ b/ghc.spec @@ -223,7 +223,7 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif -ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files +ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a %{!?with_libffi:$RPM_BUILD_ROOT%{ghclibdir}/HSffi.o} $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files # these are handled as alternatives @@ -356,7 +356,7 @@ fi %changelog * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 -- fix non shared build for ppc, etc +- fix without_shared build (thanks Adrian Reber) - disable system libffi for secondary archs - temporarily disable ghc-*-devel BRs for ppc From 7dae59527e15914f2e3e08a5f70986e76a5f8bb3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 16:42:26 +1000 Subject: [PATCH 241/530] disable testsuite for a faster build --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d4d6b48..6f7f3ca 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_without testsuite +%bcond_with testsuite # include colored html src %bcond_without hscolour # use system libffi From f4b87979c8483417f9203bbaf1ec5042a8d41206 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Feb 2011 18:16:12 +1000 Subject: [PATCH 242/530] rebuild --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6f7f3ca..68e88e3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_with testsuite +%bcond_without testsuite # include colored html src %bcond_without hscolour # use system libffi @@ -30,7 +30,7 @@ Name: ghc # NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 9%{?dist} +Release: 10%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -52,9 +52,7 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel -%ifarch %{ix86} x86_64 BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel -%endif # for internal terminfo BuildRequires: ncurses-devel Requires: gcc @@ -355,6 +353,9 @@ fi %endif %changelog +* Thu Feb 10 2011 Jens Petersen - 7.0.1-10 +- rebuild + * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 - fix without_shared build (thanks Adrian Reber) - disable system libffi for secondary archs From 5b550d30801a3baeaba57089c22a087c549d900c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 11 Feb 2011 00:57:11 +1000 Subject: [PATCH 243/530] back to the "bootstrapping" rebuild for ppc with minor bump --- ghc.spec | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 68e88e3..a4dc636 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_without testsuite +%bcond_with testsuite # include colored html src %bcond_without hscolour # use system libffi @@ -30,7 +30,7 @@ Name: ghc # NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 10%{?dist} +Release: 9.1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -52,7 +52,9 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel +%ifarch %{ix86} x86_64 BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel +%endif # for internal terminfo BuildRequires: ncurses-devel Requires: gcc @@ -353,9 +355,6 @@ fi %endif %changelog -* Thu Feb 10 2011 Jens Petersen - 7.0.1-10 -- rebuild - * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 - fix without_shared build (thanks Adrian Reber) - disable system libffi for secondary archs From 1907bb4f66fb570908009209c80db4ab43a6e891 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 11 Feb 2011 01:52:41 +1000 Subject: [PATCH 244/530] back to previous state This reverts commit f78d369c4a69e27e84e13e3add32d15603a80ff3. --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index a4dc636..68e88e3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,7 +10,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_with testsuite +%bcond_without testsuite # include colored html src %bcond_without hscolour # use system libffi @@ -30,7 +30,7 @@ Name: ghc # NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 9.1%{?dist} +Release: 10%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha @@ -52,9 +52,7 @@ Obsoletes: ghc-haddock-doc < 2.4.2-3 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 BuildRequires: gmp-devel, libffi-devel -%ifarch %{ix86} x86_64 BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel -%endif # for internal terminfo BuildRequires: ncurses-devel Requires: gcc @@ -355,6 +353,9 @@ fi %endif %changelog +* Thu Feb 10 2011 Jens Petersen - 7.0.1-10 +- rebuild + * Thu Feb 10 2011 Jens Petersen - 7.0.1-9 - fix without_shared build (thanks Adrian Reber) - disable system libffi for secondary archs From 1135618ddeecf60c408fb34523085ce5a7ef754e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 13 Feb 2011 22:53:48 +1000 Subject: [PATCH 245/530] fix singleton sed --- pkg-deps.sh | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/pkg-deps.sh b/pkg-deps.sh index 5387c43..4cb0011 100755 --- a/pkg-deps.sh +++ b/pkg-deps.sh @@ -43,7 +43,7 @@ GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list byte for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done # remove singletons -sed -i -e /^"[^ ]*"$/d pkgs.dot +sed -i -e '/^"[^ ]*"$/d' pkgs.dot which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg From 6c57433e7207e539a4a98239554d291004120741 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 13 Feb 2011 22:59:34 +1000 Subject: [PATCH 246/530] without_shared renamed to ghc_without_shared --- ghc.spec | 23 ++++++++++++----------- 1 file changed, 12 insertions(+), 11 deletions(-) diff --git a/ghc.spec b/ghc.spec index 68e88e3..58bb431 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,8 +1,6 @@ +# shared haskell library support for x86* archs from version 6.12 + ## default enabled options ## -# haskell shared library support available from 6.12 for x86* -%ifnarch %{ix86} x86_64 -%global without_shared 1 -%endif %bcond_without doc # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) @@ -22,7 +20,7 @@ # quick build profile %bcond_with quick -# the debuginfo subpackage is currently empty anyway, so don't generate it +# debuginfo is not useful for ghc %global debug_package %{nil} Name: ghc @@ -154,7 +152,7 @@ rm -r ghc-tarballs/libffi %build cat > mk/build.mk << EOF -GhcLibWays = v %{?with_prof:p} %{!?without_shared:dyn} +GhcLibWays = v %{?with_prof:p} %{!?ghc_without_shared:dyn} %if %{without doc} HADDOCK_DOCS = NO %endif @@ -182,7 +180,7 @@ export CFLAGS="${CFLAGS:-%optflags}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - %{!?without_shared:--enable-shared} + %{!?ghc_without_shared:--enable-shared} # 4 cpus or more sometimes breaks build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) @@ -196,7 +194,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?without_shared:-devel}.files +echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files done %ghc_gen_filelists ghc %{ghc_version_override} @@ -205,7 +203,7 @@ done %ghc_gen_filelists integer-gmp 0.2.0.2 %define merge_filelist()\ -%if 0%{!?without_shared:1}\ +%if %{undefined ghc_without_shared}\ cat ghc-%1.files >> ghc-%2.files\ %endif\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ @@ -217,7 +215,7 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist ghc-prim base %merge_filelist ghc-binary bin-package-db -%if 0%{!?without_shared:1} +%if %{undefined ghc_without_shared} ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif @@ -256,7 +254,7 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if 0%{!?without_shared:1} +%if %{undefined ghc_without_shared} echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] @@ -353,6 +351,9 @@ fi %endif %changelog +* Sun Feb 13 2011 Jens Petersen +- without_shared renamed to ghc_without_shared + * Thu Feb 10 2011 Jens Petersen - 7.0.1-10 - rebuild From 4b3172815b44862d7337ae3c55b7068c6c92e039 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 13 Feb 2011 23:00:35 +1000 Subject: [PATCH 247/530] hackage/ and pkgdeps.sh moved to fedorahosted haskell-sig repo --- hackage/Makefile | 7 --- hackage/f13 | 80 ---------------------------------- hackage/f14 | 88 ------------------------------------- hackage/f15 | 91 --------------------------------------- hackage/hackage-fedora.py | 37 ---------------- pkg-deps.sh | 57 ------------------------ 6 files changed, 360 deletions(-) delete mode 100644 hackage/Makefile delete mode 100644 hackage/f13 delete mode 100644 hackage/f14 delete mode 100644 hackage/f15 delete mode 100755 hackage/hackage-fedora.py delete mode 100755 pkg-deps.sh diff --git a/hackage/Makefile b/hackage/Makefile deleted file mode 100644 index 6837520..0000000 --- a/hackage/Makefile +++ /dev/null @@ -1,7 +0,0 @@ -CURRENT = f14 - -all: - ./hackage-fedora.py $(CURRENT) - -push: - scp $(CURRENT) fedorapeople.org:public_html/hackage/Fedora diff --git a/hackage/f13 b/hackage/f13 deleted file mode 100644 index 25445ee..0000000 --- a/hackage/f13 +++ /dev/null @@ -1,80 +0,0 @@ -("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") -("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") -("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") -("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") -("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") -("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") -("QuickCheck","2.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") -("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") -("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") -("alex","2.3.2",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") -("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") -("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") -("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") -("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") -("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") -("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") -("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") -("cabal-install","0.8.0",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") -("cgi","3001.1.7.2",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") -("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") -("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") -("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") -("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") -("csv","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") -("darcs","2.4.4",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") -("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") -("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") -("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") -("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") -("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") -("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") -("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") -("fgl","5.4.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") -("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") -("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") -("haddock","2.4.2",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") -("happy","1.18.4",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") -("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") -("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") -("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") -("haskell-src-exts","1.8.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") -("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") -("hlint","1.6.20",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") -("hscolour","1.16",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") -("hslogger","1.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") -("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") -("libmpd","0.4.2",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") -("mmap","0.4.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") -("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") -("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") -("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") -("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") -("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") -("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") -("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") -("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") -("regex-base","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") -("regex-compat","0.92",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") -("regex-posix","0.94.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") -("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") -("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") -("split","0.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") -("stm","2.1.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") -("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") -("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") -("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") -("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") -("text","0.10.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") -("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") -("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") -("uniplate","1.5.1",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") -("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") -("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") -("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") -("xmobar","0.11.1",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") -("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") -("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") -("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") -("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") -("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") diff --git a/hackage/f14 b/hackage/f14 deleted file mode 100644 index aacba4e..0000000 --- a/hackage/f14 +++ /dev/null @@ -1,88 +0,0 @@ -("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") -("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") -("HTTP","4000.0.9",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") -("HUnit","1.2.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") -("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") -("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") -("QuickCheck","2.1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") -("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") -("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") -("alex","2.3.3",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") -("ansi-terminal","0.5.5",Just "https://admin.fedoraproject.org/community/?package=ghc-ansi-terminal#package_maintenance") -("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") -("attoparsec","0.8.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") -("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") -("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") -("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") -("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") -("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") -("cabal-install","0.8.2",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") -("cairo","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-cairo#package_maintenance") -("cgi","3001.1.7.3",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") -("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") -("cmdargs","0.6.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") -("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") -("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") -("csv","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") -("darcs","2.4.4",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") -("dataenc","0.13.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") -("deepseq","1.1.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") -("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") -("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") -("enumerator","0.4.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") -("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") -("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") -("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") -("ghc-paths","0.1.0.6",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") -("gio","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-gio#package_maintenance") -("glade","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-glade#package_maintenance") -("glib","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-glib#package_maintenance") -("gtk","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-gtk#package_maintenance") -("gtk2hs-buildtools","0.11.2",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") -("gtksourceview2","0.12.1",Just "https://admin.fedoraproject.org/community/?package=ghc-gtksourceview2#package_maintenance") -("haddock","2.4.2",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") -("happy","1.18.5",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") -("hashed-storage","0.4.13",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") -("haskeline","0.6.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") -("haskell-src","1.0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") -("haskell-src-exts","1.9.0",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") -("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") -("hlint","1.7.3",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") -("hscolour","1.17",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") -("hslogger","1.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") -("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") -("libmpd","0.4.2",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") -("mmap","0.4.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") -("mtl","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") -("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") -("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") -("network","2.2.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") -("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") -("pango","0.11.2",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") -("parallel","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") -("parsec","2.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") -("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") -("regex-base","0.93.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") -("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") -("regex-posix","0.94.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") -("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") -("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") -("split","0.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") -("stm","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") -("tagsoup","0.11.1",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") -("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") -("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") -("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") -("text","0.10.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") -("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") -("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") -("uniplate","1.5.1",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") -("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") -("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") -("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") -("xmobar","0.11.1",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") -("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") -("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") -("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") -("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") -("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") diff --git a/hackage/f15 b/hackage/f15 deleted file mode 100644 index 8c72490..0000000 --- a/hackage/f15 +++ /dev/null @@ -1,91 +0,0 @@ -("Boolean","0.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-Boolean#package_maintenance") -("GLUT","2.1.2.1",Just "https://admin.fedoraproject.org/community/?package=ghc-GLUT#package_maintenance") -("HTTP","4000.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-HTTP#package_maintenance") -("HUnit","1.2.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-HUnit#package_maintenance") -("MissingH","1.1.0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-MissingH#package_maintenance") -("OpenGL","2.2.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-OpenGL#package_maintenance") -("QuickCheck","2.4.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-QuickCheck#package_maintenance") -("X11","1.5.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-X11#package_maintenance") -("X11-xft","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-X11-xft#package_maintenance") -("alex","2.3.4",Just "https://admin.fedoraproject.org/community/?package=alex#package_maintenance") -("ansi-terminal","0.5.5",Just "https://admin.fedoraproject.org/community/?package=ghc-ansi-terminal#package_maintenance") -("attempt","0.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attempt#package_maintenance") -("attoparsec","0.8.3.0",Just "https://admin.fedoraproject.org/community/?package=ghc-attoparsec#package_maintenance") -("base64-bytestring","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-base64-bytestring#package_maintenance") -("binary","0.5.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-binary#package_maintenance") -("blaze-builder","0.2.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-blaze-builder#package_maintenance") -("bytestring-nums","0.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-nums#package_maintenance") -("bytestring-trie","0.2.2",Just "https://admin.fedoraproject.org/community/?package=ghc-bytestring-trie#package_maintenance") -("cabal-install","0.9.5",Just "https://admin.fedoraproject.org/community/?package=cabal-install#package_maintenance") -("cairo","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-cairo#package_maintenance") -("cgi","3001.1.7.4",Just "https://admin.fedoraproject.org/community/?package=ghc-cgi#package_maintenance") -("chalmers-lava2000","1.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-chalmers-lava2000#package_maintenance") -("cmdargs","0.6.7",Just "https://admin.fedoraproject.org/community/?package=ghc-cmdargs#package_maintenance") -("colour","2.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-colour#package_maintenance") -("cpphs","1.11",Just "https://admin.fedoraproject.org/community/?package=cpphs#package_maintenance") -("csv","0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-csv#package_maintenance") -("darcs","2.5",Just "https://admin.fedoraproject.org/community/?package=darcs#package_maintenance") -("dataenc","0.13.0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-dataenc#package_maintenance") -("deepseq","1.1.0.2",Just "https://admin.fedoraproject.org/community/?package=ghc-deepseq#package_maintenance") -("digest","0.0.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-digest#package_maintenance") -("editline","0.2.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-editline#package_maintenance") -("enumerator","0.4.5",Just "https://admin.fedoraproject.org/community/?package=ghc-enumerator#package_maintenance") -("failure","0.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-failure#package_maintenance") -("feldspar-language","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-feldspar-language#package_maintenance") -("fgl","5.4.2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-fgl#package_maintenance") -("ghc-paths","0.1.0.8",Just "https://admin.fedoraproject.org/community/?package=ghc-ghc-paths#package_maintenance") -("gio","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-gio#package_maintenance") -("glade","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-glade#package_maintenance") -("glib","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-glib#package_maintenance") -("gtk","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-gtk#package_maintenance") -("gtk2hs-buildtools","0.12.0",Just "https://admin.fedoraproject.org/community/?package=gtk2hs-buildtools#package_maintenance") -("gtksourceview2","0.12.2",Just "https://admin.fedoraproject.org/community/?package=ghc-gtksourceview2#package_maintenance") -("haddock","2.9.1",Just "https://admin.fedoraproject.org/community/?package=haddock#package_maintenance") -("hamlet","0.6.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-hamlet#package_maintenance") -("happy","1.18.6",Just "https://admin.fedoraproject.org/community/?package=happy#package_maintenance") -("hashed-storage","0.5.4",Just "https://admin.fedoraproject.org/community/?package=ghc-hashed-storage#package_maintenance") -("haskeline","0.6.3.2",Just "https://admin.fedoraproject.org/community/?package=ghc-haskeline#package_maintenance") -("haskell-src","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src#package_maintenance") -("haskell-src-exts","1.9.6",Just "https://admin.fedoraproject.org/community/?package=ghc-haskell-src-exts#package_maintenance") -("hinotify","0.3.1",Just "https://admin.fedoraproject.org/community/?package=ghc-hinotify#package_maintenance") -("hlint","1.8.3",Just "https://admin.fedoraproject.org/community/?package=hlint#package_maintenance") -("hscolour","1.17",Just "https://admin.fedoraproject.org/community/?package=hscolour#package_maintenance") -("hslogger","1.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-hslogger#package_maintenance") -("html","1.0.1.2",Just "https://admin.fedoraproject.org/community/?package=ghc-html#package_maintenance") -("libmpd","0.5.0",Just "https://admin.fedoraproject.org/community/?package=ghc-libmpd#package_maintenance") -("mmap","0.5.7",Just "https://admin.fedoraproject.org/community/?package=ghc-mmap#package_maintenance") -("mtl","2.0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-mtl#package_maintenance") -("mtlparse","0.1.1",Just "https://admin.fedoraproject.org/community/?package=ghc-mtlparse#package_maintenance") -("neither","0.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-neither#package_maintenance") -("network","2.3",Just "https://admin.fedoraproject.org/community/?package=ghc-network#package_maintenance") -("pandoc","1.6.0.1",Just "https://admin.fedoraproject.org/community/?package=pandoc#package_maintenance") -("pango","0.12.0",Just "https://admin.fedoraproject.org/community/?package=ghc-pango#package_maintenance") -("parallel","3.1.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-parallel#package_maintenance") -("parsec","3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-parsec#package_maintenance") -("process-leksah","1.0.1.4",Just "https://admin.fedoraproject.org/community/?package=ghc-process-leksah#package_maintenance") -("regex-base","0.93.2",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-base#package_maintenance") -("regex-compat","0.93.1",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-compat#package_maintenance") -("regex-posix","0.94.4",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-posix#package_maintenance") -("regex-tdfa","1.1.7",Just "https://admin.fedoraproject.org/community/?package=ghc-regex-tdfa#package_maintenance") -("regexpr","0.5.3",Just "https://admin.fedoraproject.org/community/?package=ghc-regexpr#package_maintenance") -("safe","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-safe#package_maintenance") -("split","0.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-split#package_maintenance") -("stm","2.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-stm#package_maintenance") -("syb","0.3",Just "https://admin.fedoraproject.org/community/?package=ghc-syb#package_maintenance") -("tagsoup","0.12",Just "https://admin.fedoraproject.org/community/?package=ghc-tagsoup#package_maintenance") -("tar","0.3.1.0",Just "https://admin.fedoraproject.org/community/?package=ghc-tar#package_maintenance") -("terminfo","0.3.1.3",Just "https://admin.fedoraproject.org/community/?package=ghc-terminfo#package_maintenance") -("texmath","0.4",Just "https://admin.fedoraproject.org/community/?package=ghc-texmath#package_maintenance") -("text","0.11.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-text#package_maintenance") -("transformers","0.2.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-transformers#package_maintenance") -("type-level","0.2.4",Just "https://admin.fedoraproject.org/community/?package=ghc-type-level#package_maintenance") -("uniplate","1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-uniplate#package_maintenance") -("utf8-string","0.3.6",Just "https://admin.fedoraproject.org/community/?package=ghc-utf8-string#package_maintenance") -("xhtml","3000.2.0.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xhtml#package_maintenance") -("xml","1.3.7",Just "https://admin.fedoraproject.org/community/?package=ghc-xml#package_maintenance") -("xmobar","0.12",Just "https://admin.fedoraproject.org/community/?package=xmobar#package_maintenance") -("xmonad","0.9.1",Just "https://admin.fedoraproject.org/community/?package=xmonad#package_maintenance") -("xmonad-contrib","0.9.1",Just "https://admin.fedoraproject.org/community/?package=ghc-xmonad-contrib#package_maintenance") -("zip-archive","0.1.1.6",Just "https://admin.fedoraproject.org/community/?package=ghc-zip-archive#package_maintenance") -("zlib","0.5.2.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib#package_maintenance") -("zlib-bindings","0.0.0",Just "https://admin.fedoraproject.org/community/?package=ghc-zlib-bindings#package_maintenance") diff --git a/hackage/hackage-fedora.py b/hackage/hackage-fedora.py deleted file mode 100755 index 3ed9d14..0000000 --- a/hackage/hackage-fedora.py +++ /dev/null @@ -1,37 +0,0 @@ -#!/usr/bin/python - -# generates a Fedora distro package status file for hackage.haskell.org - -from fedora.client import PackageDB -import koji -import sys - -if len(sys.argv) > 1: - release = sys.argv[1] -else: - release = 'f14' - print release + ':' - -pkgdb = PackageDB() -p = pkgdb.user_packages('haskell-sig') - -# exclude packages not in Hackage -packages = [pkg['name'] for pkg in p.pkgs if pkg['name'] not in ['cabal2spec','emacs-haskell-mode','ghc','ghc-gtk2hs','ghc-rpm-macros','haskell-platform','hugs98']] - -session = koji.ClientSession('http://koji.fedoraproject.org/kojihub') - -outlist = [] - -for pkg in packages: - latest = session.getLatestBuilds('dist-' + release + '-updates', package=pkg) - if latest: - ver = latest[0]['version'] - name = pkg.replace('ghc-','',1) - print "%s-%s" % (name,ver) - result = "(\"%s\",\"%s\",Just \"https://admin.fedoraproject.org/community/?package=%s#package_maintenance\")" % (name,ver,pkg) - outlist.append(result) - -f = open(release, 'w') - -for l in sorted(outlist): - f.write(l+'\n') diff --git a/pkg-deps.sh b/pkg-deps.sh deleted file mode 100755 index 4cb0011..0000000 --- a/pkg-deps.sh +++ /dev/null @@ -1,57 +0,0 @@ -#!/bin/sh - -# script to generate dependency graph for fedora haskell libraries -# requires ghc, ghc-*-devel and graphviz to be installed - -set -e +x - -mkdir -p .pkg-deps - -cd .pkg-deps - -# remove the closing line -ghc-pkg dot --global | sed '$d' > pkgs.dot - -# check for binary deps too -# (exclude binlib for now since covered by libs): cpphs, darcs, hlint, hscolour, xmonad -for i in alex cabal-install ghc happy gtk2hs-buildtools haskell-platform hedgewars-server xmobar; do - PKG_THERE=yes - PKG=`rpm -q --qf "%{name}-%{version}" $i` || { PKG_THERE=no ; echo "missing: $i" ; } - if [ "$PKG_THERE" = "yes" ]; then - echo \"$PKG\" >> pkgs.dot - case $i in - haskell-platform) - rpm -q --requires $i | grep -v rpmlib | grep -v ghc | sed -e "s/^/\"$PKG\" -> \"/g" -e "s/ = \(.*\)/-\1\"/" >> pkgs.dot - ;; - *) - rpm -q --requires $i | grep -- -ghc | sed -e "s/libHS/\"$PKG\" -> \"/g" -e "s/-ghc.*/\"/" >> pkgs.dot - ;; - esac - fi -done - -# make sure all libs there -rpm -qa --qf "\"%{name}-%{version}\"\n" ghc-\* | egrep -v -- "(ghc-libs|-prof|-devel|-doc|rpm-macros)-" | sed -e s/^\"ghc-/\"/g >> pkgs.dot - -# and add it back -echo "}" >> pkgs.dot - -cp -p pkgs.dot pkgs.dot.orig - -# ignore library packages provided by ghc (except ghc-6.12) -GHC_PKGS="array base-4 base-3 bin-package-db $(ghc-pkg --simple-output list bytestring) Cabal containers directory dph extensible-exceptions filepath ffi ghc-binary ghc-prim haskell98 hpc integer-gmp old-locale old-time pretty process random rts syb-0.1 template-haskell time unix Win32" -for i in $GHC_PKGS; do sed -i -e /$i/d pkgs.dot; done - -# remove singletons -sed -i -e '/^"[^ ]*"$/d' pkgs.dot - -which tred &>/dev/null || { echo "graphviz is needed to generate graph" ; exit 1 ; } -cat pkgs.dot | tred | dot -Nfontsize=8 -Tsvg >pkgs.svg - -if [ -n "$DISPLAY" ]; then - xdg-open pkgs.svg -else - echo open ".pkg-deps/pkgs.svg" to display pkg graph -fi - -echo https://fedoraproject.org/wiki/Haskell_package_interdependencies From 7e6bda15065525c31cab4631013a67e2d0e3b327 Mon Sep 17 00:00:00 2001 From: "Fabio M. Di Nitto" Date: Wed, 23 Feb 2011 14:46:08 +0100 Subject: [PATCH 248/530] enable ghc build on sparcv9 Signed-off-by: Fabio M. Di Nitto --- ghc-fix-linking-on-sparc.patch | 13 +++++++++++++ ghc.spec | 17 ++++++++++++++--- 2 files changed, 27 insertions(+), 3 deletions(-) create mode 100644 ghc-fix-linking-on-sparc.patch diff --git a/ghc-fix-linking-on-sparc.patch b/ghc-fix-linking-on-sparc.patch new file mode 100644 index 0000000..323730a --- /dev/null +++ b/ghc-fix-linking-on-sparc.patch @@ -0,0 +1,13 @@ +diff -Nuard ghc-7.0.1.orig/compiler/main/DriverPipeline.hs ghc-7.0.1/compiler/main/DriverPipeline.hs +--- ghc-7.0.1.orig/compiler/main/DriverPipeline.hs 2010-11-12 19:10:03.000000000 +0100 ++++ ghc-7.0.1/compiler/main/DriverPipeline.hs 2011-02-22 11:08:26.079686994 +0100 +@@ -1211,6 +1211,9 @@ + let ld_r args = SysTools.runLink dflags ([ + SysTools.Option "-nostdlib", + SysTools.Option "-nodefaultlibs", ++#ifdef sparc_TARGET_ARCH ++ SysTools.Option "-Wl,--no-relax", ++#endif + SysTools.Option "-Wl,-r", + SysTools.Option ld_x_flag, + SysTools.Option "-o", diff --git a/ghc.spec b/ghc.spec index 58bb431..8d9c4f9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,10 +28,10 @@ Name: ghc # NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.1 # can't be reset - used by versioned library subpackages -Release: 10%{?dist} +Release: 11%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: -ExclusiveArch: %{ix86} x86_64 ppc alpha +ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -48,7 +48,7 @@ Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 -BuildRequires: ghc, ghc-rpm-macros >= 0.11.1 +BuildRequires: ghc, ghc-rpm-macros >= 0.11.10 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -72,6 +72,7 @@ Patch4: ghc-use-system-libffi.patch # add cabal configure option --enable-executable-dynamic # (see http://hackage.haskell.org/trac/hackage/ticket/600) Patch5: Cabal-option-executable-dynamic.patch +Patch6: ghc-fix-linking-on-sparc.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -150,6 +151,8 @@ rm -r ghc-tarballs/libffi %patch5 -p1 -b .orig +%patch6 -p1 -b .sparclinking + %build cat > mk/build.mk << EOF GhcLibWays = v %{?with_prof:p} %{!?ghc_without_shared:dyn} @@ -351,6 +354,14 @@ fi %endif %changelog +* Wed Feb 23 2011 Fabio M. Di Nitto +- enable build on sparcv9 +- add ghc-fix-linking-on-sparc.patch to fix ld being called + at the same time with --relax and -r. The two options conflict + on sparc. +- bump BuildRequires on ghc-rpm-macros to >= 0.11.10 that guarantees + a correct build on secondary architectures. + * Sun Feb 13 2011 Jens Petersen - without_shared renamed to ghc_without_shared From 9ccb8ffbea7521c64845b0f5b2179b9b562ff4be Mon Sep 17 00:00:00 2001 From: "Fabio M. Di Nitto" Date: Wed, 23 Feb 2011 14:49:11 +0100 Subject: [PATCH 249/530] Fix changelog version Signed-off-by: Fabio M. Di Nitto --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8d9c4f9..cd7a10e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -354,7 +354,7 @@ fi %endif %changelog -* Wed Feb 23 2011 Fabio M. Di Nitto +* Wed Feb 23 2011 Fabio M. Di Nitto 7.0.1-11 - enable build on sparcv9 - add ghc-fix-linking-on-sparc.patch to fix ld being called at the same time with --relax and -r. The two options conflict From 7dad1aa6908c85fba4aa46b132cc08f6aedc0199 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Mar 2011 13:25:14 +0900 Subject: [PATCH 250/530] update to 7.0.2 release; move bin-package-db into ghc-ghc --- ghc-use-system-libffi.patch | 4 ++-- ghc.spec | 47 +++++++++++++++++++++++-------------- 2 files changed, 31 insertions(+), 20 deletions(-) diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index 31f40c6..60262e0 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -47,9 +47,9 @@ diff -up ghc-7.0.1/ghc.mk.libffi ghc-7.0.1/ghc.mk install_packages: install_libexecs -install_packages: libffi/package.conf.install rts/package.conf.install +install_packages: rts/package.conf.install - $(INSTALL_DIR) "$(DESTDIR)$(topdir)" + $(call INSTALL_DIR,"$(DESTDIR)$(topdir)") "$(RM)" $(RM_OPTS_REC) "$(INSTALLED_PACKAGE_CONF)" - $(INSTALL_DIR) "$(INSTALLED_PACKAGE_CONF)" + $(call INSTALL_DIR,"$(INSTALLED_PACKAGE_CONF)") - "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update libffi/package.conf.install "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install $(foreach p, $(INSTALLED_PKG_DIRS), \ diff --git a/ghc.spec b/ghc.spec index cd7a10e..1b58245 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,4 @@ -# shared haskell library support for x86* archs from version 6.12 +# shared haskell libraries supported for x86* archs (enabled in ghc-rpm-macros) ## default enabled options ## %bcond_without doc @@ -8,7 +8,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_without testsuite +%bcond_with testsuite # include colored html src %bcond_without hscolour # use system libffi @@ -20,15 +20,18 @@ # quick build profile %bcond_with quick -# debuginfo is not useful for ghc +# ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} Name: ghc -# haskell-platform-2011.1.0.0 +# haskell-platform-2011.2.0.0 # NB make sure to rebuild ghc after a version bump to avoid ABI change problems -Version: 7.0.1 -# can't be reset - used by versioned library subpackages -Release: 11%{?dist} +Version: 7.0.2 +# Since library subpackages are versioned: +# - release can only be reset if all library versions get bumped simultaneously +# (eg for a major release) +# - minor release numbers should be incremented monotonically +Release: 12%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -48,7 +51,7 @@ Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 -BuildRequires: ghc, ghc-rpm-macros >= 0.11.10 +BuildRequires: ghc, ghc-rpm-macros >= 0.11.11 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -87,27 +90,28 @@ interface. %global ghc_version_override %{version} %if 0%{?ghclibdir:1} -%ghc_binlib_package Cabal 1.10.0.0 +%ghc_binlib_package Cabal 1.10.1.0 %ghc_binlib_package array 0.3.0.2 -%ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.0.0 -%ghc_binlib_package bin-package-db 0.0.0.0 -%ghc_binlib_package bytestring 0.9.1.8 +%ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.1.0 +%ghc_binlib_package bytestring 0.9.1.10 %ghc_binlib_package containers 0.4.0.0 %ghc_binlib_package directory 1.1.0.0 %ghc_binlib_package extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 +%define ghc_pkg_obsoletes ghc-bin-package-db < 0.0.0.0-12 %ghc_binlib_package -x ghc %{ghc_version_override} +%undefine ghc_pkg_obsoletes %ghc_binlib_package haskell2010 1.0.0.0 -%ghc_binlib_package haskell98 1.1.0.0 +%ghc_binlib_package haskell98 1.1.0.1 %ghc_binlib_package hpc 0.5.0.6 %ghc_binlib_package old-locale 1.0.0.2 %ghc_binlib_package old-time 1.0.0.6 %ghc_binlib_package pretty 1.0.1.2 -%ghc_binlib_package process 1.0.1.4 +%ghc_binlib_package process 1.0.1.5 %ghc_binlib_package random 1.0.0.3 %ghc_binlib_package template-haskell 2.5.0.0 %ghc_binlib_package time 1.2.0.3 -%ghc_binlib_package unix 2.4.1.0 +%ghc_binlib_package unix 2.4.2.0 %endif %global version %{ghc_version_override} @@ -197,13 +201,15 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files +# now handled by macro +#echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files done +%ghc_gen_filelists bin-package-db 0.0.0.0 %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghc-binary 0.5.0.2 %ghc_gen_filelists ghc-prim 0.2.0.0 -%ghc_gen_filelists integer-gmp 0.2.0.2 +%ghc_gen_filelists integer-gmp 0.2.0.3 %define merge_filelist()\ %if %{undefined ghc_without_shared}\ @@ -216,7 +222,8 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base -%merge_filelist ghc-binary bin-package-db +%merge_filelist ghc-binary ghc +%merge_filelist bin-package-db ghc %if %{undefined ghc_without_shared} ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files @@ -354,6 +361,10 @@ fi %endif %changelog +* Wed Mar 9 2011 Jens Petersen - 7.0.2-12 +- update to 7.0.2 release +- move bin-package-db into ghc-ghc + * Wed Feb 23 2011 Fabio M. Di Nitto 7.0.1-11 - enable build on sparcv9 - add ghc-fix-linking-on-sparc.patch to fix ld being called From 4368f60e11a1480228b5c1b36f7d7131be53315b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Mar 2011 13:34:21 +0900 Subject: [PATCH 251/530] disable broken testsuite --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index 1b58245..c1c1241 100644 --- a/ghc.spec +++ b/ghc.spec @@ -364,6 +364,7 @@ fi * Wed Mar 9 2011 Jens Petersen - 7.0.2-12 - update to 7.0.2 release - move bin-package-db into ghc-ghc +- disable broken testsuite * Wed Feb 23 2011 Fabio M. Di Nitto 7.0.1-11 - enable build on sparcv9 From 90258c43566d22a4b4882fe89ee37e4fe73131cb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Mar 2011 13:36:33 +0900 Subject: [PATCH 252/530] new source --- .gitignore | 1 + sources | 3 +-- 2 files changed, 2 insertions(+), 2 deletions(-) diff --git a/.gitignore b/.gitignore index 435f172..fb22a4d 100644 --- a/.gitignore +++ b/.gitignore @@ -2,3 +2,4 @@ ghc-6.12.3-src.tar.bz2 testsuite-6.12.3.tar.bz2 /ghc-7.0.1-src.tar.bz2 /testsuite-7.0.1.tar.bz2 +/ghc-7.0.2-src.tar.bz2 diff --git a/sources b/sources index b3abffd..f8f3d93 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -91814d1de48c661fd79ffa810026ed19 ghc-7.0.1-src.tar.bz2 -96ea44f9c0fe6552883e2aa129f3e701 testsuite-7.0.1.tar.bz2 +946a18a0dc30437db72c0d3fdf26ca42 ghc-7.0.2-src.tar.bz2 From 0e135afcf49e3a4fb11def7ee171123ec80264ce Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Mar 2011 15:28:38 +0900 Subject: [PATCH 253/530] need -devel in ghc_pkg_obsoletes --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c1c1241..a126ad9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -98,7 +98,7 @@ interface. %ghc_binlib_package directory 1.1.0.0 %ghc_binlib_package extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 -%define ghc_pkg_obsoletes ghc-bin-package-db < 0.0.0.0-12 +%define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 %ghc_binlib_package -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes %ghc_binlib_package haskell2010 1.0.0.0 From f6b392765eb1b41fa70fd08aaddc66d1e0207c2c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Mar 2011 17:22:36 +0900 Subject: [PATCH 254/530] bump for rebuild against 7.0.2 --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a126ad9..f5dfaff 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 12%{?dist} +Release: 13%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -361,6 +361,9 @@ fi %endif %changelog +* Thu Mar 10 2011 Jens Petersen - 7.0.2-13 +- rebuild against 7.0.2 + * Wed Mar 9 2011 Jens Petersen - 7.0.2-12 - update to 7.0.2 release - move bin-package-db into ghc-ghc From 2cb5dc1619248415a51ba33426727a3a51a32ac0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 25 Mar 2011 14:37:33 +0900 Subject: [PATCH 255/530] update ghc-rpm-macros BR to 0.11.12 --- ghc.spec | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index f5dfaff..eb79ff2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -51,7 +51,7 @@ Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 -BuildRequires: ghc, ghc-rpm-macros >= 0.11.11 +BuildRequires: ghc, ghc-rpm-macros >= 0.11.12 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -201,8 +201,6 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -# now handled by macro -#echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files done %ghc_gen_filelists bin-package-db 0.0.0.0 From ed9ba74656c0b35ebe99168f8909dd9a53c9d6f2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 29 Mar 2011 11:51:29 +0900 Subject: [PATCH 256/530] bring back LICENSE files to library subpackages and drop ghc_reindex_haddock --- ghc.spec | 12 ++++++++---- 1 file changed, 8 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index eb79ff2..93546c1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 13%{?dist} +Release: 14%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -145,7 +145,7 @@ They should be installed when GHC's profiling subsystem is needed. # disable gen_contents_index when not --batch for cron %patch3 -p1 -# use system libraries +# make sure we don't use these rm -r ghc-tarballs/{mingw,perl} # use system libffi %if %{with libffi} @@ -201,6 +201,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver +echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files done %ghc_gen_filelists bin-package-db 0.0.0.0 @@ -255,7 +256,7 @@ mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] -# don't seem to work inplace: +# doesn't seem to work inplace: #[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs @@ -299,7 +300,6 @@ fi %posttrans # (posttrans to make sure any old libs and docs have been removed first) %ghc_pkg_recache -%ghc_reindex_haddock %files %defattr(-,root,root,-) @@ -359,6 +359,10 @@ fi %endif %changelog +* Tue Mar 29 2011 Jens Petersen - 7.0.2-14 +- fix back missing LICENSE files in library subpackages +- drop ghc_reindex_haddock from install script + * Thu Mar 10 2011 Jens Petersen - 7.0.2-13 - rebuild against 7.0.2 From 3cd7a9e1c4b6f5557296bc3ce25e634ce2e8c214 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 30 Mar 2011 15:11:54 +0900 Subject: [PATCH 257/530] dont strip static libs (it breaks ghci-7.0.2 loading libHSghc.a); no longer provide ghc-doc nor obsolete haddock --- ghc.spec | 33 ++++++++++++++++++++++++--------- 1 file changed, 24 insertions(+), 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 93546c1..a66ea07 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,4 +1,5 @@ -# shared haskell libraries supported for x86* archs (enabled in ghc-rpm-macros) +# shared haskell libraries supported for x86* archs +# (disabled for other archs in ghc-rpm-macros) ## default enabled options ## %bcond_without doc @@ -23,6 +24,20 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} +# override /usr/lib/rpm/redhat/macros +%global __os_install_post \ + /usr/lib/rpm/redhat/brp-compress \ + %{!?__debug_package:\ + /usr/lib/rpm/redhat/brp-strip %{__strip} \ + /usr/lib/rpm/redhat/brp-strip-comment-note %{__strip} %{__objdump} \ + } \ +# Disable static stripping since it breaks loading libHSghc.a for ghc 7.0.2 and 7.0.3\ +# /usr/lib/rpm/redhat/brp-strip-static-archive %{__strip} \ + /usr/lib/rpm/brp-python-bytecompile %{__python} %{?_python_bytecompile_errors_terminate_build} \ + /usr/lib/rpm/redhat/brp-python-hardlink \ + %{!?__jar_repack:/usr/lib/rpm/redhat/brp-java-repack-jars} \ +%{nil} + Name: ghc # haskell-platform-2011.2.0.0 # NB make sure to rebuild ghc after a version bump to avoid ABI change problems @@ -31,7 +46,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 14%{?dist} +Release: 15%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -45,10 +60,6 @@ Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ # introduced for f14 Obsoletes: ghc-doc < 6.12.3-4 -Provides: ghc-doc = %{version}-%{release} -# introduced for f11 -Obsoletes: haddock < 2.4.2-3, ghc-haddock-devel < 2.4.2-3 -Obsoletes: ghc-haddock-doc < 2.4.2-3 # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.12 @@ -89,7 +100,7 @@ interface. %global ghc_version_override %{version} -%if 0%{?ghclibdir:1} +%if %{defined ghclibdir}\ %ghc_binlib_package Cabal 1.10.1.0 %ghc_binlib_package array 0.3.0.2 %ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.1.0 @@ -129,7 +140,6 @@ This is a meta-package for all the development library packages in GHC. Summary: GHC profiling libraries meta-package Group: Development/Libraries %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g")} -Obsoletes: ghc-haddock-prof < 2.4.2-3 %description prof This is a meta-package for all the profiling library packages in GHC. @@ -189,7 +199,7 @@ export CFLAGS="${CFLAGS:-%optflags}" --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ %{!?ghc_without_shared:--enable-shared} -# 4 cpus or more sometimes breaks build +# >4 cpus tends to break build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) [ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 make -j$RPM_BUILD_NCPUS @@ -359,6 +369,11 @@ fi %endif %changelog +* Wed Mar 30 2011 Jens Petersen - 7.0.2-15 +- do not strip static libs since it breaks ghci-7.0.2 loading libHSghc.a +- no longer provide ghc-doc +- no longer obsolete old haddock + * Tue Mar 29 2011 Jens Petersen - 7.0.2-14 - fix back missing LICENSE files in library subpackages - drop ghc_reindex_haddock from install script From c1bb4a88ea380bb0e7d081fc08fbfb1b99eb2357 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 30 Mar 2011 15:17:48 +0900 Subject: [PATCH 258/530] remove trailing backquote after %{defined ghclibdir} --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a66ea07..50b6ef3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -100,7 +100,7 @@ interface. %global ghc_version_override %{version} -%if %{defined ghclibdir}\ +%if %{defined ghclibdir} %ghc_binlib_package Cabal 1.10.1.0 %ghc_binlib_package array 0.3.0.2 %ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.1.0 From 37726ff38873a917ec45ed9ca2e89e1a36e06951 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Apr 2011 13:34:49 +0900 Subject: [PATCH 259/530] provides ghc-doc again; ghc-prof requires ghc-devel; ghc-devel requires ghc --- ghc.spec | 13 ++++++++++++- 1 file changed, 12 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 50b6ef3..ccb183e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -24,6 +24,7 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} +# workaround http://hackage.haskell.org/trac/ghc/ticket/5004 # override /usr/lib/rpm/redhat/macros %global __os_install_post \ /usr/lib/rpm/redhat/brp-compress \ @@ -46,7 +47,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 15%{?dist} +Release: 16%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -60,6 +61,8 @@ Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ # introduced for f14 Obsoletes: ghc-doc < 6.12.3-4 +# BR for lib and binlib packages +Provides: ghc-doc = %{version}-%{release} # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 BuildRequires: ghc, ghc-rpm-macros >= 0.11.12 @@ -130,6 +133,7 @@ interface. %package devel Summary: GHC development libraries meta package Group: Development/Libraries +Requires: ghc = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2,/g")} %description devel @@ -139,6 +143,7 @@ This is a meta-package for all the development library packages in GHC. %package prof Summary: GHC profiling libraries meta-package Group: Development/Libraries +Requires: ghc-devel = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g")} %description prof @@ -369,8 +374,14 @@ fi %endif %changelog +* Fri Apr 1 2011 Jens Petersen - 7.0.2-16 +- provides ghc-doc again: it is still a buildrequires for libraries +- ghc-prof now requires ghc-devel +- ghc-devel now requires ghc explicitly + * Wed Mar 30 2011 Jens Petersen - 7.0.2-15 - do not strip static libs since it breaks ghci-7.0.2 loading libHSghc.a + (see http://hackage.haskell.org/trac/ghc/ticket/5004) - no longer provide ghc-doc - no longer obsolete old haddock From 1ed3ce3d594fe7cf10d4a097393ac2c98344806c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Apr 2011 16:57:19 +0900 Subject: [PATCH 260/530] rebuild against ghc-rpm-macros-0.11.14 to provide ghc-*-doc --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index ccb183e..e37309f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -47,7 +47,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 16%{?dist} +Release: 17%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 @@ -374,6 +374,9 @@ fi %endif %changelog +* Fri Apr 1 2011 Jens Petersen - 7.0.2-17 +- rebuild against ghc-rpm-macros-0.11.14 to provide ghc-*-doc + * Fri Apr 1 2011 Jens Petersen - 7.0.2-16 - provides ghc-doc again: it is still a buildrequires for libraries - ghc-prof now requires ghc-devel From e48cc497d45aff55bab1d8f2dad13b3aa3565af5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 21 Apr 2011 18:24:42 +0900 Subject: [PATCH 261/530] ppc64 bootstrapping by Jiri Skala --- ghc-ppc64-pthread.patch | 18 ++++++++++++++++++ ghc.spec | 32 +++++++++++++++++++++++++++++--- 2 files changed, 47 insertions(+), 3 deletions(-) create mode 100644 ghc-ppc64-pthread.patch diff --git a/ghc-ppc64-pthread.patch b/ghc-ppc64-pthread.patch new file mode 100644 index 0000000..d317ff7 --- /dev/null +++ b/ghc-ppc64-pthread.patch @@ -0,0 +1,18 @@ +diff -up ghc-7.0.2/aclocal.m4.pthread ghc-7.0.2/aclocal.m4 +--- ghc-7.0.2/aclocal.m4.pthread 2011-02-28 13:10:03.000000000 -0500 ++++ ghc-7.0.2/aclocal.m4 2011-04-20 07:12:36.489772545 -0400 +@@ -1385,7 +1385,7 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) + dnl except we don't want to have to know what make is called. Sigh. + rm -rf utils/ghc-pwd/dist-boot + mkdir utils/ghc-pwd/dist-boot +- if ! "$WithGhc" -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd ++ if ! "$WithGhc" -optl-pthread -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd + then + AC_MSG_ERROR([Building ghc-pwd failed]) + fi +diff -up ghc-7.0.2/ghc/ghc.wrapper.pthread ghc-7.0.2/ghc/ghc.wrapper +--- ghc-7.0.2/ghc/ghc.wrapper.pthread 2011-04-20 09:58:50.307894773 -0400 ++++ ghc-7.0.2/ghc/ghc.wrapper 2011-04-20 09:59:14.477894370 -0400 +@@ -1 +1 @@ +-exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" ${1+"$@"} ++exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" -optl-pthread ${1+"$@"} diff --git a/ghc.spec b/ghc.spec index e37309f..b787a2f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -47,10 +47,10 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 17%{?dist} +Release: 18%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: -ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 +ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -82,6 +82,9 @@ BuildRequires: hscolour %if %{with testsuite} BuildRequires: python %endif +%ifarch ppc64 +BuildRequires: autoconf +%endif Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch @@ -90,6 +93,7 @@ Patch4: ghc-use-system-libffi.patch # (see http://hackage.haskell.org/trac/hackage/ticket/600) Patch5: Cabal-option-executable-dynamic.patch Patch6: ghc-fix-linking-on-sparc.patch +Patch7: ghc-ppc64-pthread.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -172,6 +176,11 @@ rm -r ghc-tarballs/libffi %patch6 -p1 -b .sparclinking +%ifarch ppc64 +%patch7 -p1 -b .pthread +%endif + + %build cat > mk/build.mk << EOF GhcLibWays = v %{?with_prof:p} %{!?ghc_without_shared:dyn} @@ -194,8 +203,20 @@ HSCOLOUR_SRCS = NO %if %{with libffi} SRC_HC_OPTS += -lffi %endif +%ifarch ppc64 +GhcUnregisterised=YES +GhcWithNativeCodeGen=NO +SplitObjs=NO +GhcWithInterpreter=NO +GhcNotThreaded=YES +SRC_HC_OPTS+=-optc-mminimal-toc -optl-pthread +SRC_CC_OPTS+=-mminimal-toc -pthread -Wa,--noexecstack +%endif EOF +%ifarch ppc64 +autoreconf +%endif export CFLAGS="${CFLAGS:-%optflags}" ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ @@ -323,9 +344,11 @@ fi %dir %{ghclibdir} %{ghclibdir}/extra-gcc-opts %{ghclibdir}/ghc -%{ghclibdir}/ghc-asm %{ghclibdir}/ghc-pkg +%ifnarch ppc64 +%{ghclibdir}/ghc-asm %{ghclibdir}/ghc-split +%endif %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt %{ghclibdir}/hsc2hs @@ -374,6 +397,9 @@ fi %endif %changelog +* Thu Apr 21 2011 Jiri Skala - 7.0.2-18 +- bootstrap to ppc64 + * Fri Apr 1 2011 Jens Petersen - 7.0.2-17 - rebuild against ghc-rpm-macros-0.11.14 to provide ghc-*-doc From a5bffe88e83f499bec27d6dec9d1864988450db6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 26 Apr 2011 17:40:21 +0900 Subject: [PATCH 262/530] add upstream ghc-powerpc-linker-mmap.patch for ppc64 (Jiri Skala) --- ghc-powerpc-linker-mmap.patch | 34 ++++++++++++++++++++++++++++++++++ ghc.spec | 8 +++++++- 2 files changed, 41 insertions(+), 1 deletion(-) create mode 100644 ghc-powerpc-linker-mmap.patch diff --git a/ghc-powerpc-linker-mmap.patch b/ghc-powerpc-linker-mmap.patch new file mode 100644 index 0000000..df0d5ff --- /dev/null +++ b/ghc-powerpc-linker-mmap.patch @@ -0,0 +1,34 @@ +diff -up ghc-7.0.2/rts/Linker.c.fix-powerpc ghc-7.0.2/rts/Linker.c +--- ghc-7.0.2/rts/Linker.c.fix-powerpc 2011-02-28 19:10:08.000000000 +0100 ++++ ghc-7.0.2/rts/Linker.c 2011-04-25 22:20:10.781092305 +0200 +@@ -70,11 +70,12 @@ + #include + #endif + +-#if defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ +- defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ +- defined(openbsd_HOST_OS ) || \ +- ( defined(darwin_HOST_OS ) && !defined(powerpc_HOST_ARCH) ) +-/* Don't use mmap on powerpc-apple-darwin as mmap doesn't support ++#if !defined(powerpc_HOST_ARCH) && \ ++ ( defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ ++ defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ ++ defined(openbsd_HOST_OS ) || defined(darwin_HOST_OS ) || \ ++ defined(kfreebsdgnu_HOST_OS) ) ++/* Don't use mmap on powerpc_HOST_ARCH as mmap doesn't support + * reallocating but we need to allocate jump islands just after each + * object images. Otherwise relative branches to jump islands can fail + * due to 24-bits displacement overflow. +@@ -2436,7 +2437,11 @@ static void ocFlushInstructionCacheFrom( + static void ocFlushInstructionCache( ObjectCode *oc ) + { + /* The main object code */ +- ocFlushInstructionCacheFrom(oc->image + oc->misalignment, oc->fileSize); ++ ocFlushInstructionCacheFrom(oc->image ++#ifdef darwin_HOST_OS ++ + oc->misalignment ++#endif ++ , oc->fileSize); + + /* Jump Islands */ + ocFlushInstructionCacheFrom(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); diff --git a/ghc.spec b/ghc.spec index b787a2f..6a6b11e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -47,7 +47,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 18%{?dist} +Release: 19%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -94,6 +94,8 @@ Patch4: ghc-use-system-libffi.patch Patch5: Cabal-option-executable-dynamic.patch Patch6: ghc-fix-linking-on-sparc.patch Patch7: ghc-ppc64-pthread.patch +# http://hackage.haskell.org/trac/ghc/ticket/4999 +Patch8: ghc-powerpc-linker-mmap.patch %description GHC is a state-of-the-art programming suite for Haskell, a purely @@ -178,6 +180,7 @@ rm -r ghc-tarballs/libffi %ifarch ppc64 %patch7 -p1 -b .pthread +%patch8 -p1 -b .mmap %endif @@ -397,6 +400,9 @@ fi %endif %changelog +* Tue Apr 26 2011 Jens Petersen - 7.0.2-19 +- upstream ghc-powerpc-linker-mmap.patch for ppc64 (Jiri Skala) + * Thu Apr 21 2011 Jiri Skala - 7.0.2-18 - bootstrap to ppc64 From ac238f56e13403998419dacf8c1762bf0c088804 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 27 Apr 2011 16:33:18 +0900 Subject: [PATCH 263/530] apply the powerpc linker patch also to ppc --- ghc.spec | 3 +++ 1 file changed, 3 insertions(+) diff --git a/ghc.spec b/ghc.spec index 6a6b11e..8b38d0a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -180,6 +180,9 @@ rm -r ghc-tarballs/libffi %ifarch ppc64 %patch7 -p1 -b .pthread +%endif + +%ifarch ppc ppc64 %patch8 -p1 -b .mmap %endif From c7d4ebf2b53b8b9f4156d7d8a27060bd8a885e98 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 2 May 2011 20:34:56 +0900 Subject: [PATCH 264/530] replace hscolour bcond by without_hscolour like in ghc-rpm-macros --- ghc.spec | 6 ++---- 1 file changed, 2 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 8b38d0a..87fca2b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,8 +10,6 @@ %bcond_without manual # run testsuite %bcond_with testsuite -# include colored html src -%bcond_without hscolour # use system libffi %ifarch %{ix86} x86_64 %bcond_without libffi @@ -76,7 +74,7 @@ Requires: ghc-base-devel %if %{with manual} BuildRequires: libxslt, docbook-style-xsl %endif -%if %{with hscolour} +%if %{undefined without_hscolour} BuildRequires: hscolour %endif %if %{with testsuite} @@ -203,7 +201,7 @@ GhcStage2HcOpts = -O0 -fasm GhcLibHcOpts = -O0 -fasm SplitObjs = NO %endif -%if %{without hscolour} +%if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif %if %{with libffi} From 712ef6ba2a7e2afa668977a73d72b1d62207d7c6 Mon Sep 17 00:00:00 2001 From: Jiri Skala Date: Wed, 4 May 2011 04:35:14 +0200 Subject: [PATCH 265/530] fixes path to gcc on ppc64 arch --- ghc.spec | 8 +++++++- 1 file changed, 7 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 87fca2b..08f19de 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,7 +45,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 19%{?dist} +Release: 19.1%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -227,6 +227,9 @@ export CFLAGS="${CFLAGS:-%optflags}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ +%ifarch ppc64 + --with-gcc=/usr/bin/gcc +%endif %{!?ghc_without_shared:--enable-shared} # >4 cpus tends to break build @@ -401,6 +404,9 @@ fi %endif %changelog +* Wed May 04 2011 Jiri Skala - 7.0.2-19.1 +- fixes path to gcc on ppc64 arch + * Tue Apr 26 2011 Jens Petersen - 7.0.2-19 - upstream ghc-powerpc-linker-mmap.patch for ppc64 (Jiri Skala) From ff4a87db24a87caef25110be07fcdcd66ef57f31 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 9 May 2011 00:17:42 +0900 Subject: [PATCH 266/530] be explicit about release for devel, prof; add explicit ghc requires for ghc-*-devel --- ghc.spec | 14 ++++++++++---- 1 file changed, 10 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 08f19de..4a500f9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,7 +45,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 19.1%{?dist} +Release: 20%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -107,6 +107,8 @@ interface. %global ghc_version_override %{version} +%global ghc_pkg_c_deps ghc = %{ghc_version_override}-%{release} + %if %{defined ghclibdir} %ghc_binlib_package Cabal 1.10.1.0 %ghc_binlib_package array 0.3.0.2 @@ -138,7 +140,7 @@ interface. Summary: GHC development libraries meta package Group: Development/Libraries Requires: ghc = %{version}-%{release} -%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2,/g")} +%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} %description devel This is a meta-package for all the development library packages in GHC. @@ -148,7 +150,7 @@ This is a meta-package for all the development library packages in GHC. Summary: GHC profiling libraries meta-package Group: Development/Libraries Requires: ghc-devel = %{version}-%{release} -%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2,/g")} +%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2-%{release},/g")} %description prof This is a meta-package for all the profiling library packages in GHC. @@ -404,11 +406,15 @@ fi %endif %changelog +* Mon May 9 2011 Jens Petersen - 7.0.2-20 +- make devel and prof meta packages require libs with release +- make ghc-*-devel subpackages require ghc with release + * Wed May 04 2011 Jiri Skala - 7.0.2-19.1 - fixes path to gcc on ppc64 arch * Tue Apr 26 2011 Jens Petersen - 7.0.2-19 -- upstream ghc-powerpc-linker-mmap.patch for ppc64 (Jiri Skala) +- add upstream ghc-powerpc-linker-mmap.patch for ppc64 (Jiri Skala) * Thu Apr 21 2011 Jiri Skala - 7.0.2-18 - bootstrap to ppc64 From 4817313fd5ab73ad6d4b29c4a62061f4a69c9012 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 11 May 2011 11:46:06 +0900 Subject: [PATCH 267/530] specify /usr/bin/gcc to help bootstrapping; drop redundant posttrans scriplet --- ghc.spec | 18 +++++++++--------- 1 file changed, 9 insertions(+), 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4a500f9..bf3996b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,7 +45,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 20%{?dist} +Release: 21%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -224,18 +224,17 @@ EOF autoreconf %endif export CFLAGS="${CFLAGS:-%optflags}" +# specify gcc to avoid problems when bootstrapping with ccache ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ -%ifarch ppc64 - --with-gcc=/usr/bin/gcc -%endif + --with-gcc=%{_bindir}/gcc \ %{!?ghc_without_shared:--enable-shared} # >4 cpus tends to break build -[ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(/usr/bin/getconf _NPROCESSORS_ONLN) +[ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(%{_bindir}/getconf _NPROCESSORS_ONLN) [ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 make -j$RPM_BUILD_NCPUS @@ -342,10 +341,6 @@ if [ "$1" = 0 ]; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi -%posttrans -# (posttrans to make sure any old libs and docs have been removed first) -%ghc_pkg_recache - %files %defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README @@ -406,6 +401,11 @@ fi %endif %changelog +* Wed May 11 2011 Jens Petersen - 7.0.2-21 +- configure with /usr/bin/gcc to help bootstrapping to new archs + (otherwise ccache tends to get hardcoded as gcc, which not in koji) +- posttrans scriplet for ghc_pkg_recache is redundant + * Mon May 9 2011 Jens Petersen - 7.0.2-20 - make devel and prof meta packages require libs with release - make ghc-*-devel subpackages require ghc with release From fab994e091e57e764b42d0128dffd2cf1be87afc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 16 May 2011 11:39:27 +0900 Subject: [PATCH 268/530] merge prof subpackages into the devel subpackages with ghc-rpm-macros-0.13 --- ghc.spec | 27 +++++++-------------------- 1 file changed, 7 insertions(+), 20 deletions(-) diff --git a/ghc.spec b/ghc.spec index bf3996b..50a81cf 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,7 +45,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 21%{?dist} +Release: 22%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -63,7 +63,7 @@ Obsoletes: ghc-doc < 6.12.3-4 Provides: ghc-doc = %{version}-%{release} # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 -BuildRequires: ghc, ghc-rpm-macros >= 0.11.12 +BuildRequires: ghc, ghc-rpm-macros >= 0.13 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -140,23 +140,13 @@ interface. Summary: GHC development libraries meta package Group: Development/Libraries Requires: ghc = %{version}-%{release} +Obsoletes: ghc-prof < %{version}-%{release} +Provides: ghc-prof = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} %description devel This is a meta-package for all the development library packages in GHC. -%if %{with prof} -%package prof -Summary: GHC profiling libraries meta-package -Group: Development/Libraries -Requires: ghc-devel = %{version}-%{release} -%{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-prof = \2-%{release},/g")} - -%description prof -This is a meta-package for all the profiling library packages in GHC. -They should be installed when GHC's profiling subsystem is needed. -%endif - %prep %setup -q -n %{name}-%{version} %{?with_testsuite:-b2} # absolute haddock path (was for html/libraries -> libraries) @@ -259,7 +249,6 @@ done cat ghc-%1.files >> ghc-%2.files\ %endif\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ -cat ghc-%1-prof.files >> ghc-%2-prof.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files @@ -395,12 +384,10 @@ fi %files devel %defattr(-,root,root,-) -%if %{with prof} -%files prof -%defattr(-,root,root,-) -%endif - %changelog +* Mon May 16 2011 Jens Petersen - 7.0.2-22 +- merge the prof subpackage into devel with ghc-rpm-macros-0.13 + * Wed May 11 2011 Jens Petersen - 7.0.2-21 - configure with /usr/bin/gcc to help bootstrapping to new archs (otherwise ccache tends to get hardcoded as gcc, which not in koji) From 13e0298b14548bddfc71adbd5cff89fc51d6e1ed Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 16 May 2011 14:10:51 +0900 Subject: [PATCH 269/530] improve the prof merge changelog entry --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 50a81cf..f93081b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -386,7 +386,7 @@ fi %changelog * Mon May 16 2011 Jens Petersen - 7.0.2-22 -- merge the prof subpackage into devel with ghc-rpm-macros-0.13 +- merge prof subpackages into the devel subpackages with ghc-rpm-macros-0.13 * Wed May 11 2011 Jens Petersen - 7.0.2-21 - configure with /usr/bin/gcc to help bootstrapping to new archs From e7caec162a822be1c68e513c4a445a9562037ad7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 21 May 2011 23:22:35 +0900 Subject: [PATCH 270/530] obsolete dph libraries and feldspar-language --- ghc.spec | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index f93081b..92f4788 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,7 +45,7 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 22%{?dist} +Release: 23%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has only been bootstrapped on the following archs: ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -63,6 +63,13 @@ Obsoletes: ghc-doc < 6.12.3-4 Provides: ghc-doc = %{version}-%{release} # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 +Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 +Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 +Obsoletes: ghc-dph-prim-interface < 0.5, ghc-dph-prim-interface-devel < 0.5, ghc-dph-interface-prim-prof < 0.5 +Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-par-prof < 0.5 +Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 +Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 +Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 BuildRequires: ghc, ghc-rpm-macros >= 0.13 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel @@ -385,6 +392,9 @@ fi %defattr(-,root,root,-) %changelog +* Sat May 21 2011 Jens Petersen - 7.0.2-23 +- obsolete dph libraries and feldspar-language + * Mon May 16 2011 Jens Petersen - 7.0.2-22 - merge prof subpackages into the devel subpackages with ghc-rpm-macros-0.13 From 58ab2dd550c9e46730193afcfeb49caa7c6aae89 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 14 Jun 2011 17:11:44 +0900 Subject: [PATCH 271/530] change from ExclusiveArch to ExcludeArch to target more archs --- ghc.spec | 10 +++++++--- 1 file changed, 7 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 92f4788..cc3ecf9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -45,10 +45,11 @@ Version: 7.0.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 23%{?dist} +Release: 24%{?dist} Summary: Glasgow Haskell Compilation system -# fedora ghc has only been bootstrapped on the following archs: -ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 +# fedora ghc has been bootstrapped on the following archs: +#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 +ExcludeArch: sparc64 s390x License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -392,6 +393,9 @@ fi %defattr(-,root,root,-) %changelog +* Tue Jun 14 2011 Jens Petersen - 7.0.2-24 +- finally change from ExclusiveArch to ExcludeArch to target more archs + * Sat May 21 2011 Jens Petersen - 7.0.2-23 - obsolete dph libraries and feldspar-language From bd28af383ed128fa04466dde5be28a41c0edb557 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Jun 2011 18:12:59 +0900 Subject: [PATCH 272/530] update to 7.0.4 bugfix release - strip static again (upstream #5004 fixed) - Cabal updated to 1.10.2.0 - re-enable testsuite --- .gitignore | 2 ++ ghc.spec | 59 ++++++++++++++++++++++++++++-------------------------- sources | 3 ++- 3 files changed, 35 insertions(+), 29 deletions(-) diff --git a/.gitignore b/.gitignore index fb22a4d..7ae39ec 100644 --- a/.gitignore +++ b/.gitignore @@ -3,3 +3,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.0.1-src.tar.bz2 /testsuite-7.0.1.tar.bz2 /ghc-7.0.2-src.tar.bz2 +/ghc-7.0.4-src.tar.bz2 +/testsuite-7.0.4.tar.bz2 diff --git a/ghc.spec b/ghc.spec index cc3ecf9..5680e47 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,7 +9,7 @@ # build xml manuals (users_guide, etc) %bcond_without manual # run testsuite -%bcond_with testsuite +%bcond_without testsuite # use system libffi %ifarch %{ix86} x86_64 %bcond_without libffi @@ -22,30 +22,15 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} -# workaround http://hackage.haskell.org/trac/ghc/ticket/5004 -# override /usr/lib/rpm/redhat/macros -%global __os_install_post \ - /usr/lib/rpm/redhat/brp-compress \ - %{!?__debug_package:\ - /usr/lib/rpm/redhat/brp-strip %{__strip} \ - /usr/lib/rpm/redhat/brp-strip-comment-note %{__strip} %{__objdump} \ - } \ -# Disable static stripping since it breaks loading libHSghc.a for ghc 7.0.2 and 7.0.3\ -# /usr/lib/rpm/redhat/brp-strip-static-archive %{__strip} \ - /usr/lib/rpm/brp-python-bytecompile %{__python} %{?_python_bytecompile_errors_terminate_build} \ - /usr/lib/rpm/redhat/brp-python-hardlink \ - %{!?__jar_repack:/usr/lib/rpm/redhat/brp-java-repack-jars} \ -%{nil} - Name: ghc -# haskell-platform-2011.2.0.0 +# haskell-platform-2011.2.0.1 # NB make sure to rebuild ghc after a version bump to avoid ABI change problems -Version: 7.0.2 +Version: 7.0.4 # Since library subpackages are versioned: # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 24%{?dist} +Release: 25%{?dist} Summary: Glasgow Haskell Compilation system # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -104,21 +89,31 @@ Patch7: ghc-ppc64-pthread.patch Patch8: ghc-powerpc-linker-mmap.patch %description -GHC is a state-of-the-art programming suite for Haskell, a purely -functional programming language. It includes an optimizing compiler -generating good code for a variety of platforms, together with an -interactive system for convenient, quick development. The -distribution includes space and time profiling facilities, a large -collection of libraries, and support for various language -extensions, including concurrency, exceptions, and a foreign language -interface. +GHC is a state-of-the-art, open source, compiler and interactive environment +for the functional language Haskell. Highlights: + +- GHC supports the entire Haskell 2010 language plus various extensions. +- GHC has particularly good support for concurrency and parallelism, + including support for Software Transactional Memory (STM). +- GHC generates fast code, particularly for concurrent programs + (check the results on the "Computer Language Benchmarks Game"). +- GHC works on several platforms including Windows, Mac, Linux, + most varieties of Unix, and several different processor architectures. +- GHC has extensive optimisation capabilities, + including inter-module optimisation. +- GHC compiles Haskell code either directly to native code or using LLVM + as a back-end. GHC can also generate C code as an intermediate target for + porting to new platforms. The interactive environment compiles Haskell to + bytecode, and supports execution of mixed bytecode/compiled programs. +- Profiling is supported, both by time/allocation and heap profiling. +- GHC comes with core libraries, and thousands more are available on Hackage. %global ghc_version_override %{version} %global ghc_pkg_c_deps ghc = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_binlib_package Cabal 1.10.1.0 +%ghc_binlib_package Cabal 1.10.2.0 %ghc_binlib_package array 0.3.0.2 %ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.1.0 %ghc_binlib_package bytestring 0.9.1.10 @@ -186,6 +181,8 @@ rm -r ghc-tarballs/libffi %build +# http://hackage.haskell.org/trac/ghc/wiki/Platforms +# cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF GhcLibWays = v %{?with_prof:p} %{!?ghc_without_shared:dyn} %if %{without doc} @@ -393,6 +390,12 @@ fi %defattr(-,root,root,-) %changelog +* Thu Jun 16 2011 Jens Petersen - 7.0.4-25 +- update to 7.0.4 bugfix release +- strip static again (upstream #5004 fixed) +- Cabal updated to 1.10.2.0 +- re-enable testsuite + * Tue Jun 14 2011 Jens Petersen - 7.0.2-24 - finally change from ExclusiveArch to ExcludeArch to target more archs diff --git a/sources b/sources index f8f3d93..5c31c12 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ -946a18a0dc30437db72c0d3fdf26ca42 ghc-7.0.2-src.tar.bz2 +f167b0b4538d1a56788f43fcc662b568 ghc-7.0.4-src.tar.bz2 +1680925a557821d7e3abab368f37fbdc testsuite-7.0.4.tar.bz2 From 4b97fdc10362ca3437a6148637ed589cdaf1c237 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Jun 2011 18:16:39 +0900 Subject: [PATCH 273/530] update summary in addition to description --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5680e47..2f78457 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,7 @@ Version: 7.0.4 # (eg for a major release) # - minor release numbers should be incremented monotonically Release: 25%{?dist} -Summary: Glasgow Haskell Compilation system +Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 ExcludeArch: sparc64 s390x @@ -395,6 +395,7 @@ fi - strip static again (upstream #5004 fixed) - Cabal updated to 1.10.2.0 - re-enable testsuite +- update summary and description * Tue Jun 14 2011 Jens Petersen - 7.0.2-24 - finally change from ExclusiveArch to ExcludeArch to target more archs From f7cf28625c458f789337d96bdf95216a38ae1d7b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 14:11:07 +0900 Subject: [PATCH 274/530] add ghc_bootstrap build mode - add ghc_bootstrap build mode using: ghc_without_shared, without_prof, without_haddock, without_manual, without_testsuite - add libffi_archs - use ghc-rpm-macros-0.13.4 for ghc_check_bootstrap - drop the quick build profile --- ghc.spec | 78 ++++++++++++++++++++++++++++++-------------------------- 1 file changed, 42 insertions(+), 36 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2f78457..440adf2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,23 +1,20 @@ -# shared haskell libraries supported for x86* archs +# Shared haskell libraries are supported for x86* archs # (disabled for other archs in ghc-rpm-macros) -## default enabled options ## -%bcond_without doc +# bootstrap build skips shared and prof libs, documentation, and testsuite +%if %{defined ghc_bootstrap} # test builds can made faster and smaller by disabling profiled libraries # (currently libHSrts_thr_p.a breaks no prof build) -%bcond_without prof -# build xml manuals (users_guide, etc) -%bcond_without manual -# run testsuite -%bcond_without testsuite -# use system libffi -%ifarch %{ix86} x86_64 -%bcond_without libffi +%global ghc_without_shared 1 +%global without_prof 1 +%global without_haddock 1 +# docbook manuals (users_guide, etc) +%global without_manual 1 +%global without_testsuite 1 %endif -## default disabled options ## -# quick build profile -%bcond_with quick +# archs that use system libffi +%global libffi_archs %{ix86} x86_64 # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} @@ -30,7 +27,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 25%{?dist} +Release: 26%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -38,7 +35,7 @@ ExcludeArch: sparc64 s390x License: BSD Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 -%if %{with testsuite} +%if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 %endif Source3: ghc-doc-index.cron @@ -56,7 +53,8 @@ Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-pa Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 -BuildRequires: ghc, ghc-rpm-macros >= 0.13 +BuildRequires: ghc %{!?ghc_bootstrap: = %{version}} +BuildRequires: ghc-rpm-macros >= 0.13.4 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -64,13 +62,13 @@ BuildRequires: ncurses-devel Requires: gcc Requires: ghc-base-devel # llvm is an optional dependency -%if %{with manual} +%if %{undefined without_manual} BuildRequires: libxslt, docbook-style-xsl %endif %if %{undefined without_hscolour} BuildRequires: hscolour %endif -%if %{with testsuite} +%if %{undefined without_testsuite} BuildRequires: python %endif %ifarch ppc64 @@ -151,7 +149,7 @@ Provides: ghc-prof = %{version}-%{release} This is a meta-package for all the development library packages in GHC. %prep -%setup -q -n %{name}-%{version} %{?with_testsuite:-b2} +%setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} # absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig # type-level too big so skip it in gen_contents_index @@ -162,7 +160,7 @@ This is a meta-package for all the development library packages in GHC. # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} # use system libffi -%if %{with libffi} +%ifarch %{libffi_archs} %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi %endif @@ -181,27 +179,24 @@ rm -r ghc-tarballs/libffi %build +%if %{undefined ghc_bootstrap} +%ghc_check_bootstrap +%endif + # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF -GhcLibWays = v %{?with_prof:p} %{!?ghc_without_shared:dyn} -%if %{without doc} +GhcLibWays = v %{!?without_prof:p} %{!?ghc_without_shared:dyn} +%if %{defined without_haddock} HADDOCK_DOCS = NO %endif -%if %{without manual} +%if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif -%if %{with quick} -SRC_HC_OPTS = -H64m -O0 -fasm -GhcStage1HcOpts = -O -fasm -GhcStage2HcOpts = -O0 -fasm -GhcLibHcOpts = -O0 -fasm -SplitObjs = NO -%endif %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif -%if %{with libffi} +%ifarch %{libffi_archs} SRC_HC_OPTS += -lffi %endif %ifarch ppc64 @@ -266,7 +261,10 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif -ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a %{!?with_libffi:$RPM_BUILD_ROOT%{ghclibdir}/HSffi.o} $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files +ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files +%ifnarch %{libffi_archs} +echo $RPM_BUILD_ROOT%{ghclibdir}/HSffi.o >> ghc-base-devel.files +%endif sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files # these are handled as alternatives @@ -280,7 +278,7 @@ done %ghc_strip_dynlinked -%if %{with doc} +%if %{undefined without_haddock} mkdir -p ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly install -p --mode=755 %SOURCE3 ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p ${RPM_BUILD_ROOT}%{_localstatedir}/lib/ghc @@ -307,7 +305,7 @@ inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* %endif -%if %{with testsuite} +%if %{undefined without_testsuite} make -C testsuite/tests/ghc-regress fast %endif @@ -365,7 +363,7 @@ fi %dir %{ghcdocbasedir} %if %{with doc} %{ghcdocbasedir}/html -%if %{with manual} +%if %{undefined without_manual} %{ghcdocbasedir}/Cabal %{ghcdocbasedir}/haddock %{ghcdocbasedir}/users_guide @@ -390,6 +388,14 @@ fi %defattr(-,root,root,-) %changelog +* Fri Jun 17 2011 Jens Petersen - 7.0.4-26 +- packaging cleanup: +- add ghc_bootstrap build mode using: ghc_without_shared, without_prof, + without_haddock, without_manual, without_testsuite +- add libffi_archs +- use ghc-rpm-macros-0.13.4 for ghc_check_bootstrap +- drop the quick build profile + * Thu Jun 16 2011 Jens Petersen - 7.0.4-25 - update to 7.0.4 bugfix release - strip static again (upstream #5004 fixed) From c8aa77d0065dbc45c7921b01fd2a82b32cfb3aea Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 14:32:54 +0900 Subject: [PATCH 275/530] don't need to condition ghc_check_bootstrap --- ghc.spec | 3 --- 1 file changed, 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 440adf2..c9e9dae 100644 --- a/ghc.spec +++ b/ghc.spec @@ -179,9 +179,7 @@ rm -r ghc-tarballs/libffi %build -%if %{undefined ghc_bootstrap} %ghc_check_bootstrap -%endif # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -389,7 +387,6 @@ fi %changelog * Fri Jun 17 2011 Jens Petersen - 7.0.4-26 -- packaging cleanup: - add ghc_bootstrap build mode using: ghc_without_shared, without_prof, without_haddock, without_manual, without_testsuite - add libffi_archs From 30b20cedcb3f1bcb1875391091d90d95de5c07ac Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 14:56:34 +0900 Subject: [PATCH 276/530] drop ghc_check_bootstrap for now until work out why failing in koji --- ghc.spec | 5 +---- 1 file changed, 1 insertion(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index c9e9dae..28142b0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -54,7 +54,7 @@ Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-se Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 BuildRequires: ghc %{!?ghc_bootstrap: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13.4 +BuildRequires: ghc-rpm-macros >= 0.13 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -179,8 +179,6 @@ rm -r ghc-tarballs/libffi %build -%ghc_check_bootstrap - # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF @@ -390,7 +388,6 @@ fi - add ghc_bootstrap build mode using: ghc_without_shared, without_prof, without_haddock, without_manual, without_testsuite - add libffi_archs -- use ghc-rpm-macros-0.13.4 for ghc_check_bootstrap - drop the quick build profile * Thu Jun 16 2011 Jens Petersen - 7.0.4-25 From 7caa495ea7a4e30f626c354d9f2f5224a252b8eb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 18:19:04 +0900 Subject: [PATCH 277/530] add new bootstrapping mode using ghc_bootstrap (ghc-rpm-macros-0.13.5) - BR same ghc version unless ghc_bootstrapping defined - use ghc_check_bootstrap - put dyn before p in GhcLibWays --- ghc.spec | 30 +++++++++++++----------------- 1 file changed, 13 insertions(+), 17 deletions(-) diff --git a/ghc.spec b/ghc.spec index 28142b0..df549e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,17 +1,10 @@ # Shared haskell libraries are supported for x86* archs # (disabled for other archs in ghc-rpm-macros) -# bootstrap build skips shared and prof libs, documentation, and testsuite -%if %{defined ghc_bootstrap} -# test builds can made faster and smaller by disabling profiled libraries -# (currently libHSrts_thr_p.a breaks no prof build) -%global ghc_without_shared 1 -%global without_prof 1 -%global without_haddock 1 -# docbook manuals (users_guide, etc) -%global without_manual 1 -%global without_testsuite 1 -%endif +# to bootstrap a new version of ghc, uncomment the following: +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_hscolour 1 # archs that use system libffi %global libffi_archs %{ix86} x86_64 @@ -53,8 +46,8 @@ Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-pa Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 -BuildRequires: ghc %{!?ghc_bootstrap: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13 +BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} +BuildRequires: ghc-rpm-macros >= 0.13.4 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -65,7 +58,7 @@ Requires: ghc-base-devel %if %{undefined without_manual} BuildRequires: libxslt, docbook-style-xsl %endif -%if %{undefined without_hscolour} +%if %{undefined without_haddock} && %{undefined without_hscolour} BuildRequires: hscolour %endif %if %{undefined without_testsuite} @@ -179,10 +172,12 @@ rm -r ghc-tarballs/libffi %build +%ghc_check_bootstrap + # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF -GhcLibWays = v %{!?without_prof:p} %{!?ghc_without_shared:dyn} +GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif @@ -385,10 +380,11 @@ fi %changelog * Fri Jun 17 2011 Jens Petersen - 7.0.4-26 -- add ghc_bootstrap build mode using: ghc_without_shared, without_prof, - without_haddock, without_manual, without_testsuite +- BR same ghc version unless ghc_bootstrapping defined - add libffi_archs +- use ghc-rpm-macros-0.13.4 for ghc_check_bootstrap - drop the quick build profile +- put dyn before p in GhcLibWays * Thu Jun 16 2011 Jens Petersen - 7.0.4-25 - update to 7.0.4 bugfix release From e95b4c3b725618a9cbb8cffeaec099655576c22d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 18:25:02 +0900 Subject: [PATCH 278/530] bump ghc-rpm-macros --- ghc.spec | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index df549e2..7037bd4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -47,7 +47,7 @@ Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-se Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13.4 +BuildRequires: ghc-rpm-macros >= 0.13.5 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -382,9 +382,10 @@ fi * Fri Jun 17 2011 Jens Petersen - 7.0.4-26 - BR same ghc version unless ghc_bootstrapping defined - add libffi_archs -- use ghc-rpm-macros-0.13.4 for ghc_check_bootstrap +- use ghc_check_bootstrap - drop the quick build profile - put dyn before p in GhcLibWays +- explain new bootstrapping mode using ghc_bootstrap (ghc-rpm-macros-0.13.5) * Thu Jun 16 2011 Jens Petersen - 7.0.4-25 - update to 7.0.4 bugfix release From 9b90dceff11440e06b7646343b8c3e8f54c1a91a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 18:35:15 +0900 Subject: [PATCH 279/530] skip failing ghc_check_bootstrap for now --- ghc.spec | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7037bd4..a4b7674 100644 --- a/ghc.spec +++ b/ghc.spec @@ -172,7 +172,7 @@ rm -r ghc-tarballs/libffi %build -%ghc_check_bootstrap +#%%ghc_check_bootstrap # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -382,7 +382,6 @@ fi * Fri Jun 17 2011 Jens Petersen - 7.0.4-26 - BR same ghc version unless ghc_bootstrapping defined - add libffi_archs -- use ghc_check_bootstrap - drop the quick build profile - put dyn before p in GhcLibWays - explain new bootstrapping mode using ghc_bootstrap (ghc-rpm-macros-0.13.5) From c56e3d687ada5ffbb23c79fd23562e2cca430b04 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Jun 2011 22:22:22 +0900 Subject: [PATCH 280/530] fix one last old %{with doc} --- ghc.spec | 10 ++++------ 1 file changed, 4 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index a4b7674..d13fbf8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -339,11 +339,6 @@ fi %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt %{ghclibdir}/hsc2hs -%if %{with doc} -%{ghclibdir}/haddock -%{ghclibdir}/html -%{ghclibdir}/latex -%endif %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/runghc @@ -352,7 +347,10 @@ fi %{_mandir}/man1/ghc.* %dir %{_docdir}/ghc %dir %{ghcdocbasedir} -%if %{with doc} +%if %{undefined without_haddock} +%{ghclibdir}/haddock +%{ghclibdir}/html +%{ghclibdir}/latex %{ghcdocbasedir}/html %if %{undefined without_manual} %{ghcdocbasedir}/Cabal From 8165701637be73fee1b5208a65e6a58592bea971 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 14 Sep 2011 16:12:47 +0900 Subject: [PATCH 281/530] setup ghc-deps.sh here now since no longer in %ghc_package_devel --- ghc.spec | 27 ++++++++++++++++++++------- 1 file changed, 20 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index d13fbf8..a3031c1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,26 +1,37 @@ # Shared haskell libraries are supported for x86* archs # (disabled for other archs in ghc-rpm-macros) -# to bootstrap a new version of ghc, uncomment the following: +# To bootstrap a new version of ghc, uncomment the following: #%%global ghc_bootstrapping 1 #%%{?ghc_bootstrap} #%%global without_hscolour 1 +# To do a test build instead with shared libs, uncomment the following: +#%%global ghc_bootstrapping 1 +#%%{?ghc_test} +#%%global without_hscolour 1 + # archs that use system libffi %global libffi_archs %{ix86} x86_64 # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} +%if %{defined ghc_bootstrapping} +%global _use_internal_dependency_generator 0 +%global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} +%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} +%endif + Name: ghc -# haskell-platform-2011.2.0.1 +# part of haskell-platform # NB make sure to rebuild ghc after a version bump to avoid ABI change problems Version: 7.0.4 # Since library subpackages are versioned: # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 26%{?dist} +Release: 27%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -172,8 +183,6 @@ rm -r ghc-tarballs/libffi %build -#%%ghc_check_bootstrap - # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF @@ -211,8 +220,7 @@ export CFLAGS="${CFLAGS:-%optflags}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc \ - %{!?ghc_without_shared:--enable-shared} + --with-gcc=%{_bindir}/gcc # >4 cpus tends to break build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(%{_bindir}/getconf _NPROCESSORS_ONLN) @@ -377,6 +385,10 @@ fi %defattr(-,root,root,-) %changelog +* Wed Sep 14 2011 Jens Petersen - 7.0.4-27 +- setup dependency generation with ghc-deps.sh since it was moved to + ghc_lib_install in ghc-rpm-macros + * Fri Jun 17 2011 Jens Petersen - 7.0.4-26 - BR same ghc version unless ghc_bootstrapping defined - add libffi_archs @@ -386,6 +398,7 @@ fi * Thu Jun 16 2011 Jens Petersen - 7.0.4-25 - update to 7.0.4 bugfix release + http://haskell.org/ghc/docs/7.0.4/html/users_guide/release-7-0-4.html - strip static again (upstream #5004 fixed) - Cabal updated to 1.10.2.0 - re-enable testsuite From 3ee1a50ebf34ea4bf52d50839da24f6ab49ef017 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 14 Sep 2011 17:16:02 +0900 Subject: [PATCH 282/530] setup ghc-deps.sh when not bootstrapping\! --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index a3031c1..0bf2ec7 100644 --- a/ghc.spec +++ b/ghc.spec @@ -17,7 +17,7 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} -%if %{defined ghc_bootstrapping} +%if %{undefined ghc_bootstrapping} %global _use_internal_dependency_generator 0 %global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} @@ -31,7 +31,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 27%{?dist} +Release: 28%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 @@ -385,6 +385,9 @@ fi %defattr(-,root,root,-) %changelog +* Wed Sep 14 2011 Jens Petersen - 7.0.4-28 +- setup ghc-deps.sh when not bootstrapping! + * Wed Sep 14 2011 Jens Petersen - 7.0.4-27 - setup dependency generation with ghc-deps.sh since it was moved to ghc_lib_install in ghc-rpm-macros From 1c9d41c9a0f8f37a90f87957fe8eae8f1a332aa2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 28 Sep 2011 11:33:44 +0900 Subject: [PATCH 283/530] =?UTF-8?q?port=20to=20armv7hl=20by=20Henrik=20Nor?= =?UTF-8?q?dstr=C3=B6m=20(#741725)?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- ghc.spec | 19 ++++++++++++------- 1 file changed, 12 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 0bf2ec7..63e16a0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,6 +14,9 @@ # archs that use system libffi %global libffi_archs %{ix86} x86_64 +# unregisterized archs +%global unregisterised_archs ppc64 armv7hl + # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} @@ -31,10 +34,10 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 28%{?dist} +Release: 29%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: -#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 +#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl ExcludeArch: sparc64 s390x License: BSD Group: Development/Languages @@ -199,11 +202,10 @@ HSCOLOUR_SRCS = NO %ifarch %{libffi_archs} SRC_HC_OPTS += -lffi %endif -%ifarch ppc64 +%ifarch %{unregisterised_archs} GhcUnregisterised=YES -GhcWithNativeCodeGen=NO -SplitObjs=NO -GhcWithInterpreter=NO +%endif +%ifarch ppc64 GhcNotThreaded=YES SRC_HC_OPTS+=-optc-mminimal-toc -optl-pthread SRC_CC_OPTS+=-mminimal-toc -pthread -Wa,--noexecstack @@ -340,7 +342,7 @@ fi %{ghclibdir}/extra-gcc-opts %{ghclibdir}/ghc %{ghclibdir}/ghc-pkg -%ifnarch ppc64 +%ifnarch %{unregisterised_archs} %{ghclibdir}/ghc-asm %{ghclibdir}/ghc-split %endif @@ -385,6 +387,9 @@ fi %defattr(-,root,root,-) %changelog +* Wed Sep 28 2011 Jens Petersen - 7.0.4-29 +- port to armv7hl by Henrik Nordström (#741725) + * Wed Sep 14 2011 Jens Petersen - 7.0.4-28 - setup ghc-deps.sh when not bootstrapping! From 34566cea6b57c1cfc219b882b0fb95e1afc5e570 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 29 Sep 2011 15:42:49 +0900 Subject: [PATCH 284/530] =?UTF-8?q?no=20need=20to=20specify=20-lffi=20in?= =?UTF-8?q?=20build.mk=20(Henrik=20Nordstr=C3=B6m)?= MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit --- ghc.spec | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 63e16a0..059b38f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -11,7 +11,10 @@ #%%{?ghc_test} #%%global without_hscolour 1 -# archs that use system libffi +# faster: +#%%global without_testsuite 1 + +# archs that use system libffi (needs fixing for secondary archs) %global libffi_archs %{ix86} x86_64 # unregisterized archs @@ -34,7 +37,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 29%{?dist} +Release: 30%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -199,9 +202,6 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif -%ifarch %{libffi_archs} -SRC_HC_OPTS += -lffi -%endif %ifarch %{unregisterised_archs} GhcUnregisterised=YES %endif @@ -387,6 +387,9 @@ fi %defattr(-,root,root,-) %changelog +* Thu Sep 29 2011 Jens Petersen - 7.0.4-30 +- no need to specify -lffi in build.mk (Henrik Nordström) + * Wed Sep 28 2011 Jens Petersen - 7.0.4-29 - port to armv7hl by Henrik Nordström (#741725) From 6e0974a4ffafd69760dbdd246fe16b10fb11ed2a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 30 Sep 2011 11:15:57 +0900 Subject: [PATCH 285/530] use ghc-rpm-macros-0.13.11 to fix devel subpackages' provides/obsoletes versions --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 059b38f..291ad34 100644 --- a/ghc.spec +++ b/ghc.spec @@ -37,7 +37,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 30%{?dist} +Release: 31%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -64,7 +64,7 @@ Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-se Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13.5 +BuildRequires: ghc-rpm-macros >= 0.13.11 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -387,6 +387,10 @@ fi %defattr(-,root,root,-) %changelog +* Fri Sep 30 2011 Jens Petersen - 7.0.4-31 +- build with ghc-rpm-macros >= 0.13.11 to fix provides and obsoletes versions + in library devel subpackages + * Thu Sep 29 2011 Jens Petersen - 7.0.4-30 - no need to specify -lffi in build.mk (Henrik Nordström) From 97b6c582e12ba388043d0662206b704d98cbf2f4 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Marcela=20Ma=C5=A1l=C3=A1=C5=88ov=C3=A1?= Date: Tue, 11 Oct 2011 09:45:13 +0200 Subject: [PATCH 286/530] rebuild with new gmp --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 291ad34..3fd644c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -37,7 +37,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 31%{?dist} +Release: 31%{?dist}.1 Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -387,6 +387,9 @@ fi %defattr(-,root,root,-) %changelog +* Tue Oct 11 2011 Peter Schiffer - 7.0.4-31.1 +- rebuild with new gmp + * Fri Sep 30 2011 Jens Petersen - 7.0.4-31 - build with ghc-rpm-macros >= 0.13.11 to fix provides and obsoletes versions in library devel subpackages From dac3677f692373e2eea0779ad2b26d30b1b89a2a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 17 Oct 2011 14:17:35 +0900 Subject: [PATCH 287/530] remove libffi_archs and include ghci lib in ghc-devel --- ghc.spec | 16 ++++++---------- 1 file changed, 6 insertions(+), 10 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3fd644c..8ffa6db 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,9 +14,6 @@ # faster: #%%global without_testsuite 1 -# archs that use system libffi (needs fixing for secondary archs) -%global libffi_archs %{ix86} x86_64 - # unregisterized archs %global unregisterised_archs ppc64 armv7hl @@ -37,7 +34,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 31%{?dist}.1 +Release: 32%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -130,7 +127,7 @@ for the functional language Haskell. Highlights: %ghc_binlib_package extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 -%ghc_binlib_package -x ghc %{ghc_version_override} +%ghc_binlib_package ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes %ghc_binlib_package haskell2010 1.0.0.0 %ghc_binlib_package haskell98 1.1.0.1 @@ -170,10 +167,8 @@ This is a meta-package for all the development library packages in GHC. # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} # use system libffi -%ifarch %{libffi_archs} %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi -%endif %patch5 -p1 -b .orig @@ -263,9 +258,6 @@ ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files %endif ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files -%ifnarch %{libffi_archs} -echo $RPM_BUILD_ROOT%{ghclibdir}/HSffi.o >> ghc-base-devel.files -%endif sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files # these are handled as alternatives @@ -387,6 +379,10 @@ fi %defattr(-,root,root,-) %changelog +* Mon Oct 17 2011 Jens Petersen - 7.0.4-32 +- remove libffi_archs: not allowed to bundle system libraries in Fedora +- include the ghc (ghci) library in ghc-devel + * Tue Oct 11 2011 Peter Schiffer - 7.0.4-31.1 - rebuild with new gmp From 3b165859c5b9e2fec4dcd691ed3e45bd79d8a258 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 17 Oct 2011 15:31:53 +0900 Subject: [PATCH 288/530] improve system libffi changelog comment --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8ffa6db..66ef51e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -380,7 +380,7 @@ fi %changelog * Mon Oct 17 2011 Jens Petersen - 7.0.4-32 -- remove libffi_archs: not allowed to bundle system libraries in Fedora +- remove libffi_archs: not allowed to bundle libffi on any arch - include the ghc (ghci) library in ghc-devel * Tue Oct 11 2011 Peter Schiffer - 7.0.4-31.1 From a92bbae95a87095652cf65cfcc8b3f459f3534e7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 18 Oct 2011 18:15:34 +0900 Subject: [PATCH 289/530] add armv5tel and use ghc-deps.sh when bootstrapping --- ghc.spec | 14 +++++++------- 1 file changed, 7 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 66ef51e..601b9ea 100644 --- a/ghc.spec +++ b/ghc.spec @@ -15,16 +15,14 @@ #%%global without_testsuite 1 # unregisterized archs -%global unregisterised_archs ppc64 armv7hl +%global unregisterised_archs ppc64 armv7hl armv5tel # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} -%if %{undefined ghc_bootstrapping} %global _use_internal_dependency_generator 0 %global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} -%endif Name: ghc # part of haskell-platform @@ -34,7 +32,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 32%{?dist} +Release: 33%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -61,7 +59,7 @@ Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-se Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13.11 +BuildRequires: ghc-rpm-macros >= 0.13.13 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -327,7 +325,6 @@ if [ "$1" = 0 ]; then fi %files -%defattr(-,root,root,-) %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* %dir %{ghclibdir} @@ -376,9 +373,12 @@ fi %endif %files devel -%defattr(-,root,root,-) %changelog +* Tue Oct 18 2011 Jens Petersen - 7.0.4-33 +- add armv5tel (ported by Henrik Nordström) +- also use ghc-deps.sh when bootstrapping (ghc-rpm-macros-0.13.13) + * Mon Oct 17 2011 Jens Petersen - 7.0.4-32 - remove libffi_archs: not allowed to bundle libffi on any arch - include the ghc (ghci) library in ghc-devel From 8fec83d59fcf6017ca108c3ed684b15d6f712efe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 20 Oct 2011 10:19:50 +0900 Subject: [PATCH 290/530] setup ghc-deps.sh after ghc_version_override for bootstrapping --- ghc.spec | 15 ++++++++++----- 1 file changed, 10 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 601b9ea..e576af6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,10 +20,6 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} -%global _use_internal_dependency_generator 0 -%global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} -%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} - Name: ghc # part of haskell-platform # NB make sure to rebuild ghc after a version bump to avoid ABI change problems @@ -32,7 +28,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 33%{?dist} +Release: 34%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -113,6 +109,12 @@ for the functional language Haskell. Highlights: %global ghc_version_override %{version} +# needs ghc_version_override for bootstrapping +%global _use_internal_dependency_generator 0 +%global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} +%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} + + %global ghc_pkg_c_deps ghc = %{ghc_version_override}-%{release} %if %{defined ghclibdir} @@ -375,6 +377,9 @@ fi %files devel %changelog +* Thu Oct 20 2011 Jens Petersen - 7.0.4-34 +- setup ghc-deps.sh after ghc_version_override for bootstrapping + * Tue Oct 18 2011 Jens Petersen - 7.0.4-33 - add armv5tel (ported by Henrik Nordström) - also use ghc-deps.sh when bootstrapping (ghc-rpm-macros-0.13.13) From b71ee975681c873400d44abb18051b132c28dd97 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Marcela=20Ma=C5=A1l=C3=A1=C5=88ov=C3=A1?= Date: Thu, 20 Oct 2011 19:23:08 +0200 Subject: [PATCH 291/530] rebuild with new gmp without compat lib --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index e576af6..c384e3f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,7 +28,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 34%{?dist} +Release: 34%{?dist}.1 Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -377,6 +377,9 @@ fi %files devel %changelog +* Thu Oct 20 2011 Marcela Mašláňová - 7.0.4-34.1 +- rebuild with new gmp without compat lib + * Thu Oct 20 2011 Jens Petersen - 7.0.4-34 - setup ghc-deps.sh after ghc_version_override for bootstrapping From 4946c18c2974d85bce28804d7860a0f1c5442e47 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 28 Oct 2011 18:14:37 +0900 Subject: [PATCH 292/530] add HaskellReport license tag to subpackages with Haskell Report code --- ghc.spec | 33 ++++++++++++++++++++------------- 1 file changed, 20 insertions(+), 13 deletions(-) diff --git a/ghc.spec b/ghc.spec index c384e3f..df3e888 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,7 +28,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 34%{?dist}.1 +Release: 35%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -117,26 +117,29 @@ for the functional language Haskell. Highlights: %global ghc_pkg_c_deps ghc = %{ghc_version_override}-%{release} +%define space %(echo -n ' ') +%define BSDHaskellReport BSD%{space}and%{space}HaskellReport + %if %{defined ghclibdir} %ghc_binlib_package Cabal 1.10.2.0 -%ghc_binlib_package array 0.3.0.2 -%ghc_binlib_package -c gmp-devel,libffi-devel base 4.3.1.0 +%ghc_binlib_package -l %BSDHaskellReport array 0.3.0.2 +%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel,libffi-devel base 4.3.1.0 %ghc_binlib_package bytestring 0.9.1.10 -%ghc_binlib_package containers 0.4.0.0 -%ghc_binlib_package directory 1.1.0.0 -%ghc_binlib_package extensible-exceptions 0.1.1.2 +%ghc_binlib_package -l %BSDHaskellReport containers 0.4.0.0 +%ghc_binlib_package -l %BSDHaskellReport directory 1.1.0.0 +%ghc_binlib_package -l %BSDHaskellReport extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 %ghc_binlib_package ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_binlib_package haskell2010 1.0.0.0 -%ghc_binlib_package haskell98 1.1.0.1 +%ghc_binlib_package -l HaskellReport haskell2010 1.0.0.0 +%ghc_binlib_package -l HaskellReport haskell98 1.1.0.1 %ghc_binlib_package hpc 0.5.0.6 -%ghc_binlib_package old-locale 1.0.0.2 -%ghc_binlib_package old-time 1.0.0.6 +%ghc_binlib_package -l %BSDHaskellReport old-locale 1.0.0.2 +%ghc_binlib_package -l %BSDHaskellReport old-time 1.0.0.6 %ghc_binlib_package pretty 1.0.1.2 -%ghc_binlib_package process 1.0.1.5 -%ghc_binlib_package random 1.0.0.3 +%ghc_binlib_package -l %BSDHaskellReport process 1.0.1.5 +%ghc_binlib_package -l %BSDHaskellReport random 1.0.0.3 %ghc_binlib_package template-haskell 2.5.0.0 %ghc_binlib_package time 1.2.0.3 %ghc_binlib_package unix 2.4.2.0 @@ -377,6 +380,10 @@ fi %files devel %changelog +* Fri Oct 28 2011 Jens Petersen - 7.0.4-35 +- add HaskellReport license tag to some of the library subpackages + which contain some code from the Haskell Reports + * Thu Oct 20 2011 Marcela Mašláňová - 7.0.4-34.1 - rebuild with new gmp without compat lib @@ -389,7 +396,7 @@ fi * Mon Oct 17 2011 Jens Petersen - 7.0.4-32 - remove libffi_archs: not allowed to bundle libffi on any arch -- include the ghc (ghci) library in ghc-devel +- include the ghc (ghci) library in ghc-devel (Narasim) * Tue Oct 11 2011 Peter Schiffer - 7.0.4-31.1 - rebuild with new gmp From a853f17f88caec5905867ab242be279798cf3353 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 28 Oct 2011 19:09:35 +0900 Subject: [PATCH 293/530] rebuild in the right dist tag --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index df3e888..9a418e4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -28,7 +28,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 35%{?dist} +Release: 35%{?dist}.1 Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -380,6 +380,9 @@ fi %files devel %changelog +* Fri Oct 28 2011 Jens Petersen - 7.0.4-35.1 +- rebuild against new gmp + * Fri Oct 28 2011 Jens Petersen - 7.0.4-35 - add HaskellReport license tag to some of the library subpackages which contain some code from the Haskell Reports From 717fb32ec93a01c150078478ce57f8d27e71ab8a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 1 Nov 2011 21:27:14 +0900 Subject: [PATCH 294/530] move compiler and tools to ghc-compiler, and make ghc metapackage for all ghc --- ghc.spec | 36 ++++++++++++++++++++++++++---------- 1 file changed, 26 insertions(+), 10 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9a418e4..f36b802 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,8 +10,6 @@ #%%global ghc_bootstrapping 1 #%%{?ghc_test} #%%global without_hscolour 1 - -# faster: #%%global without_testsuite 1 # unregisterized archs @@ -28,7 +26,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 35%{?dist}.1 +Release: 36%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -43,8 +41,6 @@ Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ # introduced for f14 Obsoletes: ghc-doc < 6.12.3-4 -# BR for lib and binlib packages -Provides: ghc-doc = %{version}-%{release} # introduced for f15 Obsoletes: ghc-libs < 7.0.1-3 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 @@ -60,9 +56,6 @@ BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo BuildRequires: ncurses-devel -Requires: gcc -Requires: ghc-base-devel -# llvm is an optional dependency %if %{undefined without_manual} BuildRequires: libxslt, docbook-style-xsl %endif @@ -75,6 +68,8 @@ BuildRequires: python %ifarch ppc64 BuildRequires: autoconf %endif +Requires: ghc-compiler = %{version}-%{release} +Requires: ghc-devel = %{version}-%{release} Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch @@ -115,7 +110,7 @@ for the functional language Haskell. Highlights: %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} -%global ghc_pkg_c_deps ghc = %{ghc_version_override}-%{release} +%global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %define space %(echo -n ' ') %define BSDHaskellReport BSD%{space}and%{space}HaskellReport @@ -147,10 +142,23 @@ for the functional language Haskell. Highlights: %global version %{ghc_version_override} +%package compiler +Summary: GHC compiler and utilities +Group: Development/Languages +Requires: gcc +Requires: ghc-base-devel +# llvm is an optional dependency + +%description compiler +The package contains the GHC compiler, tools and utilities. + +The ghc libraries are provided by ghc-devel. +To install all of ghc, install the ghc base package. + %package devel Summary: GHC development libraries meta package Group: Development/Libraries -Requires: ghc = %{version}-%{release} +Requires: ghc-compiler = %{version}-%{release} Obsoletes: ghc-prof < %{version}-%{release} Provides: ghc-prof = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} @@ -330,6 +338,8 @@ if [ "$1" = 0 ]; then fi %files + +%files compiler %doc ANNOUNCE HACKING LICENSE README %{_bindir}/* %dir %{ghclibdir} @@ -380,6 +390,12 @@ fi %files devel %changelog +* Tue Nov 1 2011 Jens Petersen - 7.0.4-36 +- move compiler and tools to ghc-compiler +- the ghc base package is now a metapackage that installs all of ghc, + ie ghc-compiler and ghc-devel (#750317) +- drop ghc-doc provides + * Fri Oct 28 2011 Jens Petersen - 7.0.4-35.1 - rebuild against new gmp From 30442b566428cbd556265527cc94824c1fabb10a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 Nov 2011 13:12:03 +0900 Subject: [PATCH 295/530] rename ghc-devel metapackage to ghc-libraries and require ghc-rpm-macros-0.14 --- ghc.spec | 43 +++++++++++++++++++++++++------------------ 1 file changed, 25 insertions(+), 18 deletions(-) diff --git a/ghc.spec b/ghc.spec index f36b802..daaf1c4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 36%{?dist} +Release: 37%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -50,8 +50,9 @@ Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-pa Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 +# change to ghc-compiler once backported BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} -BuildRequires: ghc-rpm-macros >= 0.13.13 +BuildRequires: ghc-rpm-macros >= 0.14 BuildRequires: gmp-devel, libffi-devel BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel # for internal terminfo @@ -69,7 +70,7 @@ BuildRequires: python BuildRequires: autoconf %endif Requires: ghc-compiler = %{version}-%{release} -Requires: ghc-devel = %{version}-%{release} +Requires: ghc-libraries = %{version}-%{release} Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch @@ -102,6 +103,19 @@ for the functional language Haskell. Highlights: - Profiling is supported, both by time/allocation and heap profiling. - GHC comes with core libraries, and thousands more are available on Hackage. +%package compiler +Summary: GHC compiler and utilities +Group: Development/Languages +Requires: gcc +Requires: ghc-base-devel +# llvm is an optional dependency + +%description compiler +The package contains the GHC compiler, tools and utilities. + +The ghc libraries are provided by ghc-devel. +To install all of ghc, install the ghc base package. + %global ghc_version_override %{version} # needs ghc_version_override for bootstrapping @@ -142,28 +156,17 @@ for the functional language Haskell. Highlights: %global version %{ghc_version_override} -%package compiler -Summary: GHC compiler and utilities -Group: Development/Languages -Requires: gcc -Requires: ghc-base-devel -# llvm is an optional dependency - -%description compiler -The package contains the GHC compiler, tools and utilities. - -The ghc libraries are provided by ghc-devel. -To install all of ghc, install the ghc base package. - -%package devel +%package libraries Summary: GHC development libraries meta package Group: Development/Libraries Requires: ghc-compiler = %{version}-%{release} +Obsoletes: ghc-devel < %{version}-%{release} +Provides: ghc-devel = %{version}-%{release} Obsoletes: ghc-prof < %{version}-%{release} Provides: ghc-prof = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} -%description devel +%description libraries This is a meta-package for all the development library packages in GHC. %prep @@ -390,6 +393,10 @@ fi %files devel %changelog +* Wed Nov 2 2011 Jens Petersen - 7.0.4-37 +- rename ghc-devel metapackage to ghc-libraries +- require ghc-rpm-macros-0.14 + * Tue Nov 1 2011 Jens Petersen - 7.0.4-36 - move compiler and tools to ghc-compiler - the ghc base package is now a metapackage that installs all of ghc, From 0cc183c6d52f6610b4f9a219c8f559db4425ef0c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 Nov 2011 13:15:00 +0900 Subject: [PATCH 296/530] also rename %files devel to libraries --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index daaf1c4..019877a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -390,7 +390,7 @@ fi %{_localstatedir}/lib/ghc %endif -%files devel +%files libraries %changelog * Wed Nov 2 2011 Jens Petersen - 7.0.4-37 From ea8cd3dfb42a0349e0160553240a634eb14b7024 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 10 Nov 2011 18:23:09 +0900 Subject: [PATCH 297/530] make the post and postun scripts now be for the compiler subpackage --- ghc.spec | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 019877a..3076222 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,7 +26,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 37%{?dist} +Release: 38%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -316,7 +316,7 @@ rm testghc/* make -C testsuite/tests/ghc-regress fast %endif -%post +%post compiler # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: # @@ -334,7 +334,7 @@ update-alternatives --install %{_bindir}/runhaskell runhaskell \ update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ %{_bindir}/hsc2hs-ghc 500 -%preun +%preun compiler if [ "$1" = 0 ]; then update-alternatives --remove runhaskell %{_bindir}/runghc update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc @@ -393,6 +393,9 @@ fi %files libraries %changelog +* Thu Nov 10 2011 Jens Petersen - 7.0.4-38 +- the post and postun scripts are now for the compiler subpackage + * Wed Nov 2 2011 Jens Petersen - 7.0.4-37 - rename ghc-devel metapackage to ghc-libraries - require ghc-rpm-macros-0.14 From c44fb9d5d219caf8516512cd6bcad0f5a5bf28f2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 14 Nov 2011 12:09:28 +0900 Subject: [PATCH 298/530] move ghc-doc and ghc-libs obsoletes; add HaskellReport license to base and libraries subpackages --- ghc.spec | 24 +++++++++++++++--------- 1 file changed, 15 insertions(+), 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3076222..7567513 100644 --- a/ghc.spec +++ b/ghc.spec @@ -18,6 +18,9 @@ # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} +%global space %(echo -n ' ') +%global BSDHaskellReport BSD%{space}and%{space}HaskellReport + Name: ghc # part of haskell-platform # NB make sure to rebuild ghc after a version bump to avoid ABI change problems @@ -26,12 +29,12 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 38%{?dist} +Release: 39%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl ExcludeArch: sparc64 s390x -License: BSD +License: %BSDHaskellReport Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} @@ -39,10 +42,6 @@ Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 %endif Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ -# introduced for f14 -Obsoletes: ghc-doc < 6.12.3-4 -# introduced for f15 -Obsoletes: ghc-libs < 7.0.1-3 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 Obsoletes: ghc-dph-prim-interface < 0.5, ghc-dph-prim-interface-devel < 0.5, ghc-dph-interface-prim-prof < 0.5 @@ -105,9 +104,12 @@ for the functional language Haskell. Highlights: %package compiler Summary: GHC compiler and utilities +License: BSD Group: Development/Languages Requires: gcc Requires: ghc-base-devel +# added in f14 +Obsoletes: ghc-doc < 6.12.3-4 # llvm is an optional dependency %description compiler @@ -126,9 +128,6 @@ To install all of ghc, install the ghc base package. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} -%define space %(echo -n ' ') -%define BSDHaskellReport BSD%{space}and%{space}HaskellReport - %if %{defined ghclibdir} %ghc_binlib_package Cabal 1.10.2.0 %ghc_binlib_package -l %BSDHaskellReport array 0.3.0.2 @@ -158,12 +157,15 @@ To install all of ghc, install the ghc base package. %package libraries Summary: GHC development libraries meta package +License: %BSDHaskellReport Group: Development/Libraries Requires: ghc-compiler = %{version}-%{release} Obsoletes: ghc-devel < %{version}-%{release} Provides: ghc-devel = %{version}-%{release} Obsoletes: ghc-prof < %{version}-%{release} Provides: ghc-prof = %{version}-%{release} +# since f15 +Obsoletes: ghc-libs < 7.0.1-3 %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} %description libraries @@ -393,6 +395,10 @@ fi %files libraries %changelog +* Sat Nov 12 2011 Jens Petersen - 7.0.4-39 +- move ghc-doc and ghc-libs obsoletes +- add HaskellReport license also to the base and libraries subpackages + * Thu Nov 10 2011 Jens Petersen - 7.0.4-38 - the post and postun scripts are now for the compiler subpackage From 2c22ffcaafe68f083eb87e01a378b9d8d79019b5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 14 Nov 2011 19:29:08 +0900 Subject: [PATCH 299/530] fix alternatives usage to follow Packaging:Alternatives (#753661) --- ghc.spec | 25 +++++++++++++++++++++++-- 1 file changed, 23 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7567513..08ffd2b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 39%{?dist} +Release: 40%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -108,6 +108,8 @@ License: BSD Group: Development/Languages Requires: gcc Requires: ghc-base-devel +Requires(post): chkconfig +Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 # llvm is an optional dependency @@ -283,6 +285,7 @@ for i in hsc2hs runhaskell; do else mv ${RPM_BUILD_ROOT}%{_bindir}/$i{,-ghc} fi + touch ${RPM_BUILD_ROOT}%{_bindir}/$i done %ghc_strip_dynlinked @@ -346,7 +349,21 @@ fi %files compiler %doc ANNOUNCE HACKING LICENSE README -%{_bindir}/* +%{_bindir}/ghc +%{_bindir}/ghc-%{version} +%{_bindir}/ghc-pkg +%{_bindir}/ghc-pkg-%{version} +%{_bindir}/ghci +%{_bindir}/ghci-%{version} +%{_bindir}/haddock +%{_bindir}/haddock-ghc-%{version} +%{_bindir}/hp2ps +%{_bindir}/hpc +%ghost %{_bindir}/hsc2hs-ghc +%{_bindir}/hsc2hs-ghc +%{_bindir}/runghc +%ghost %{_bindir}/runhaskell +%{_bindir}/runhaskell-ghc %dir %{ghclibdir} %{ghclibdir}/extra-gcc-opts %{ghclibdir}/ghc @@ -395,6 +412,10 @@ fi %files libraries %changelog +* Mon Nov 14 2011 Jens Petersen - 7.0.4-40 +- do alternatives handling correctly (reported by Giam Teck Choon, #753661) + see https://fedoraproject.org/wiki/Packaging:Alternatives + * Sat Nov 12 2011 Jens Petersen - 7.0.4-39 - move ghc-doc and ghc-libs obsoletes - add HaskellReport license also to the base and libraries subpackages From 4a103796d90f68462ba201368aacdbd08d650662 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 15 Nov 2011 09:06:42 +0900 Subject: [PATCH 300/530] fix the ghost listing of hsc2hs --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 08ffd2b..d0c1f31 100644 --- a/ghc.spec +++ b/ghc.spec @@ -359,7 +359,7 @@ fi %{_bindir}/haddock-ghc-%{version} %{_bindir}/hp2ps %{_bindir}/hpc -%ghost %{_bindir}/hsc2hs-ghc +%ghost %{_bindir}/hsc2hs %{_bindir}/hsc2hs-ghc %{_bindir}/runghc %ghost %{_bindir}/runhaskell From 5fb7b394dee3302cac098105961e2378d7dc92a6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 15 Nov 2011 09:21:18 +0900 Subject: [PATCH 301/530] move listing of haddock into conditional doc block --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index d0c1f31..135b0f0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -355,8 +355,6 @@ fi %{_bindir}/ghc-pkg-%{version} %{_bindir}/ghci %{_bindir}/ghci-%{version} -%{_bindir}/haddock -%{_bindir}/haddock-ghc-%{version} %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -384,6 +382,8 @@ fi %dir %{_docdir}/ghc %dir %{ghcdocbasedir} %if %{undefined without_haddock} +%{_bindir}/haddock +%{_bindir}/haddock-ghc-%{version} %{ghclibdir}/haddock %{ghclibdir}/html %{ghclibdir}/latex From 0432ff8ec7fe01be3c82a46bcd039e0d8076a4a8 Mon Sep 17 00:00:00 2001 From: Dennis Gilmore Date: Thu, 12 Jan 2012 21:19:12 -0600 Subject: [PATCH 302/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_17_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 135b0f0..dfc43b9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 40%{?dist} +Release: 41%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl @@ -412,6 +412,9 @@ fi %files libraries %changelog +* Fri Jan 13 2012 Fedora Release Engineering - 7.0.4-41 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_17_Mass_Rebuild + * Mon Nov 14 2011 Jens Petersen - 7.0.4-40 - do alternatives handling correctly (reported by Giam Teck Choon, #753661) see https://fedoraproject.org/wiki/Packaging:Alternatives From 80a3e4101e8805cac48639c23fe97c428f5759bc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 19 Jan 2012 12:13:37 +0900 Subject: [PATCH 303/530] move ghc-ghc-devel from ghc-libraries to the ghc metapackage --- ghc.spec | 16 +++++++++++----- 1 file changed, 11 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index dfc43b9..12d56c3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,10 +29,10 @@ Version: 7.0.4 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 41%{?dist} +Release: 42%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: -#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl +#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel ExcludeArch: sparc64 s390x License: %BSDHaskellReport Group: Development/Languages @@ -49,7 +49,7 @@ Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-pa Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 -# change to ghc-compiler once backported +# change to ghc-compiler once backported to el6 BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} BuildRequires: ghc-rpm-macros >= 0.14 BuildRequires: gmp-devel, libffi-devel @@ -70,6 +70,7 @@ BuildRequires: autoconf %endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} +Requires: ghc-ghc-devel = %{version}-%{release} Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch @@ -140,7 +141,8 @@ To install all of ghc, install the ghc base package. %ghc_binlib_package -l %BSDHaskellReport extensible-exceptions 0.1.1.2 %ghc_binlib_package filepath 1.2.0.0 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 -%ghc_binlib_package ghc %{ghc_version_override} +# in ghc not ghc-libraries: +%ghc_binlib_package -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes %ghc_binlib_package -l HaskellReport haskell2010 1.0.0.0 %ghc_binlib_package -l HaskellReport haskell98 1.1.0.1 @@ -171,7 +173,8 @@ Obsoletes: ghc-libs < 7.0.1-3 %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} %description libraries -This is a meta-package for all the development library packages in GHC. +This is a meta-package for all the development library packages in GHC +except the ghc library, which is installed by the toplevel ghc metapackage. %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} @@ -412,6 +415,9 @@ fi %files libraries %changelog +* Thu Jan 19 2012 Jens Petersen - 7.0.4-42 +- move ghc-ghc-devel from ghc-libraries to the ghc metapackage + * Fri Jan 13 2012 Fedora Release Engineering - 7.0.4-41 - Rebuilt for https://fedoraproject.org/wiki/Fedora_17_Mass_Rebuild From 56ca87f87c962fca17bf8dd4ba3d70200700e02b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Feb 2012 10:46:28 +0900 Subject: [PATCH 304/530] update to new 7.4.1 major release (still doesn't build: system libffi patch seems incomplete - can't find the libffi headers) --- .gitignore | 2 + Cabal-fix-dynamic-exec-for-TH.patch | 33 ++++++ Cabal-option-executable-dynamic.patch | 145 ------------------------- ghc-fix-linking-on-sparc.patch | 13 --- ghc-use-system-libffi.patch | 150 +++++++------------------- ghc.spec | 85 ++++++++------- sources | 4 +- 7 files changed, 127 insertions(+), 305 deletions(-) create mode 100644 Cabal-fix-dynamic-exec-for-TH.patch delete mode 100644 Cabal-option-executable-dynamic.patch delete mode 100644 ghc-fix-linking-on-sparc.patch diff --git a/.gitignore b/.gitignore index 7ae39ec..fb09fbc 100644 --- a/.gitignore +++ b/.gitignore @@ -5,3 +5,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.0.2-src.tar.bz2 /ghc-7.0.4-src.tar.bz2 /testsuite-7.0.4.tar.bz2 +/ghc-7.4.1-testsuite.tar.bz2 +/ghc-7.4.1-src.tar.bz2 diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch new file mode 100644 index 0000000..5384ea7 --- /dev/null +++ b/Cabal-fix-dynamic-exec-for-TH.patch @@ -0,0 +1,33 @@ +diff -u ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs.orig ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs +--- ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs.orig 2011-07-29 02:12:09.000000000 +0900 ++++ ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs 2011-08-05 18:08:05.192042529 +0900 +@@ -778,7 +778,10 @@ + ++ ["-L"++libDir | libDir <- extraLibDirs exeBi] + ++ concat [["-framework", f] | f <- PD.frameworks exeBi] + ++ if dynExe +- then ["-dynamic"] ++ then ["-dynamic", ++ "-hisuf", "dyn_hi", ++ "-osuf", "dyn_o" ++ ] + else [] + ++ if profExe + then ["-prof", +@@ -787,13 +790,14 @@ + ] ++ ghcProfOptions exeBi + else [] + +- -- For building exe's for profiling that use TH we actually ++ -- For building exe's for profiling or dynamic that use TH we actually + -- have to build twice, once without profiling and the again + -- with profiling. This is because the code that TH needs to + -- run at compile time needs to be the vanilla ABI so it can + -- be loaded up and run by the compiler. +- when (withProfExe lbi && EnableExtension TemplateHaskell `elem` allExtensions exeBi) +- (runGhcProg (binArgs False (withDynExe lbi) False)) ++ when ((withProfExe lbi || withDynExe lbi) && ++ EnableExtension TemplateHaskell `elem` allExtensions exeBi) ++ (runGhcProg (binArgs False False False)) + + runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi)) + diff --git a/Cabal-option-executable-dynamic.patch b/Cabal-option-executable-dynamic.patch deleted file mode 100644 index 4324c11..0000000 --- a/Cabal-option-executable-dynamic.patch +++ /dev/null @@ -1,145 +0,0 @@ -diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs ---- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs 2011-01-22 14:49:22.000000000 +1000 -+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Configure.hs 2011-01-22 14:49:22.000000000 +1000 -@@ -488,6 +488,7 @@ - withVanillaLib = fromFlag $ configVanillaLib cfg, - withProfLib = fromFlag $ configProfLib cfg, - withSharedLib = fromFlag $ configSharedLib cfg, -+ withDynExe = fromFlag $ configDynExe cfg, - withProfExe = fromFlag $ configProfExe cfg, - withOptimization = fromFlag $ configOptimization cfg, - withGHCiLib = fromFlag $ configGHCiLib cfg, -diff -u ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs ---- ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs.orig 2010-11-13 04:10:09.000000000 +1000 -+++ ghc-7.0.1/libraries/Cabal/Distribution/Simple/GHC.hs 2011-01-22 14:52:52.000000000 +1000 -@@ -537,6 +537,7 @@ - info verbosity "Building C Sources..." - sequence_ [do let (odir,args) = constructCcCmdLine lbi libBi clbi pref - filename verbosity -+ False - (withProfLib lbi) - createDirectoryIfMissingVerbose verbosity True odir - runGhcProg args -@@ -671,7 +672,7 @@ - info verbosity "Building C Sources." - sequence_ [do let (odir,args) = constructCcCmdLine lbi exeBi clbi - exeDir filename verbosity -- (withProfExe lbi) -+ (withDynExe lbi) (withProfExe lbi) - createDirectoryIfMissingVerbose verbosity True odir - runGhcProg args - | filename <- cSources exeBi] -@@ -679,7 +680,7 @@ - srcMainFile <- findFile (exeDir : hsSourceDirs exeBi) modPath - - let cObjs = map (`replaceExtension` objExtension) (cSources exeBi) -- let binArgs linkExe profExe = -+ let binArgs linkExe dynExe profExe = - "--make" - : (if linkExe - then ["-o", targetDir exeNameReal] -@@ -691,6 +692,9 @@ - ++ ["-l"++lib | lib <- extraLibs exeBi] - ++ ["-L"++libDir | libDir <- extraLibDirs exeBi] - ++ concat [["-framework", f] | f <- PD.frameworks exeBi] -+ ++ if dynExe -+ then ["-dynamic"] -+ else [] - ++ if profExe - then ["-prof", - "-hisuf", "p_hi", -@@ -704,9 +708,9 @@ - -- run at compile time needs to be the vanilla ABI so it can - -- be loaded up and run by the compiler. - when (withProfExe lbi && TemplateHaskell `elem` allExtensions exeBi) -- (runGhcProg (binArgs False False)) -+ (runGhcProg (binArgs (withDynExe lbi) False False)) - -- runGhcProg (binArgs True (withProfExe lbi)) -+ runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi)) - - -- | Filter the "-threaded" flag when profiling as it does not - -- work with ghc-6.8 and older. -@@ -836,9 +840,9 @@ - ierror = error ("internal error: unexpected package db stack: " ++ show dbstack) - - constructCcCmdLine :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -- -> FilePath -> FilePath -> Verbosity -> Bool -+ -> FilePath -> FilePath -> Verbosity -> Bool -> Bool - ->(FilePath,[String]) --constructCcCmdLine lbi bi clbi pref filename verbosity profiling -+constructCcCmdLine lbi bi clbi pref filename verbosity dynamic profiling - = let odir | compilerVersion (compiler lbi) >= Version [6,4,1] [] = pref - | otherwise = pref takeDirectory filename - -- ghc 6.4.1 fixed a bug in -odir handling -@@ -852,6 +856,7 @@ - -- option to ghc here when compiling C code, so that the PROFILING - -- macro gets defined. The macro is used in ghc's Rts.h in the - -- definitions of closure layouts (Closures.h). -+ ++ ["-dynamic" | dynamic] - ++ ["-prof" | profiling]) - - ghcCcOptions :: LocalBuildInfo -> BuildInfo -> ComponentLocalBuildInfo -diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs ---- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs 2011-01-22 14:49:22.000000000 +1000 -+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/LocalBuildInfo.hs 2011-01-22 14:49:22.000000000 +1000 -@@ -118,6 +118,7 @@ - withVanillaLib:: Bool, -- ^Whether to build normal libs. - withProfLib :: Bool, -- ^Whether to build profiling versions of libs. - withSharedLib :: Bool, -- ^Whether to build shared versions of libs. -+ withDynExe :: Bool, -- ^Whether to link executables dynamically - withProfExe :: Bool, -- ^Whether to build executables for profiling. - withOptimization :: OptimisationLevel, -- ^Whether to build with optimization (if available). - withGHCiLib :: Bool, -- ^Whether to build libs suitable for use with GHCi. -diff -rN -u old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs ---- old-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs 2011-01-22 14:49:22.000000000 +1000 -+++ new-ghc-7.0.1/libraries/Cabal/Distribution/Simple/Setup.hs 2011-01-22 14:49:22.000000000 +1000 -@@ -270,6 +270,7 @@ - configVanillaLib :: Flag Bool, -- ^Enable vanilla library - configProfLib :: Flag Bool, -- ^Enable profiling in the library - configSharedLib :: Flag Bool, -- ^Build shared library -+ configDynExe :: Flag Bool, -- ^Enable dynamic linking of the executables. - configProfExe :: Flag Bool, -- ^Enable profiling in the executables. - configConfigureArgs :: [String], -- ^Extra arguments to @configure@ - configOptimization :: Flag OptimisationLevel, -- ^Enable optimization. -@@ -301,6 +302,7 @@ - configVanillaLib = Flag True, - configProfLib = Flag False, - configSharedLib = Flag False, -+ configDynExe = Flag False, - configProfExe = Flag False, - configOptimization = Flag NormalOptimisation, - configProgPrefix = Flag (toPathTemplate ""), -@@ -388,10 +390,16 @@ - configSharedLib (\v flags -> flags { configSharedLib = v }) - (boolOpt [] []) - -+ ,option "" ["executable-dynamic"] -+ "Executable dynamic linking (fedora patch)" -+ configDynExe (\v flags -> flags { configDynExe = v }) -+ (boolOpt [] []) -+ - ,option "" ["executable-profiling"] - "Executable profiling" - configProfExe (\v flags -> flags { configProfExe = v }) - (boolOpt [] []) -+ - ,multiOption "optimization" - configOptimization (\v flags -> flags { configOptimization = v }) - [optArg' "n" (Flag . flagToOptimisationLevel) -@@ -553,6 +561,7 @@ - configVanillaLib = mempty, - configProfLib = mempty, - configSharedLib = mempty, -+ configDynExe = mempty, - configProfExe = mempty, - configConfigureArgs = mempty, - configOptimization = mempty, -@@ -583,6 +592,7 @@ - configVanillaLib = combine configVanillaLib, - configProfLib = combine configProfLib, - configSharedLib = combine configSharedLib, -+ configDynExe = combine configDynExe, - configProfExe = combine configProfExe, - configConfigureArgs = combine configConfigureArgs, - configOptimization = combine configOptimization, diff --git a/ghc-fix-linking-on-sparc.patch b/ghc-fix-linking-on-sparc.patch deleted file mode 100644 index 323730a..0000000 --- a/ghc-fix-linking-on-sparc.patch +++ /dev/null @@ -1,13 +0,0 @@ -diff -Nuard ghc-7.0.1.orig/compiler/main/DriverPipeline.hs ghc-7.0.1/compiler/main/DriverPipeline.hs ---- ghc-7.0.1.orig/compiler/main/DriverPipeline.hs 2010-11-12 19:10:03.000000000 +0100 -+++ ghc-7.0.1/compiler/main/DriverPipeline.hs 2011-02-22 11:08:26.079686994 +0100 -@@ -1211,6 +1211,9 @@ - let ld_r args = SysTools.runLink dflags ([ - SysTools.Option "-nostdlib", - SysTools.Option "-nodefaultlibs", -+#ifdef sparc_TARGET_ARCH -+ SysTools.Option "-Wl,--no-relax", -+#endif - SysTools.Option "-Wl,-r", - SysTools.Option ld_x_flag, - SysTools.Option "-o", diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index 60262e0..cac9e42 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -1,39 +1,11 @@ -diff -up ghc-7.0.1/compiler/ghc.cabal.in.libffi ghc-7.0.1/compiler/ghc.cabal.in ---- ghc-7.0.1/compiler/ghc.cabal.in.libffi 2010-11-13 04:10:03.000000000 +1000 -+++ ghc-7.0.1/compiler/ghc.cabal.in 2010-11-16 19:04:28.000000000 +1000 -@@ -83,7 +83,7 @@ Library - if flag(ghci) - Build-Depends: template-haskell - CPP-Options: -DGHCI -- Include-Dirs: ../libffi/build/include -+ pkgconfig-depends: libffi - - if !flag(ncg) - CPP-Options: -DOMIT_NATIVE_CODEGEN -diff -up ghc-7.0.1/ghc.mk.libffi ghc-7.0.1/ghc.mk ---- ghc-7.0.1/ghc.mk.libffi 2010-11-13 04:10:05.000000000 +1000 -+++ ghc-7.0.1/ghc.mk 2010-11-16 19:04:28.000000000 +1000 -@@ -437,7 +437,6 @@ utils/runghc/dist/package-data.mk: compi - # add the final two package.conf dependencies: ghc-prim depends on RTS, - # and RTS depends on libffi. - libraries/ghc-prim/dist-install/package-data.mk : rts/package.conf.inplace --rts/package.conf.inplace : libffi/package.conf.inplace - endif - - # -------------------------------- -@@ -452,11 +451,6 @@ ALL_STAGE1_LIBS += $(foreach lib,$(PACKA - endif - BOOT_LIBS = $(foreach lib,$(STAGE0_PACKAGES),$(libraries/$(lib)_dist-boot_v_LIB)) - --OTHER_LIBS = libffi/dist-install/build/libHSffi$(v_libsuf) libffi/dist-install/build/HSffi.o --ifeq "$(BuildSharedLibs)" "YES" --OTHER_LIBS += libffi/dist-install/build/libHSffi$(dyn_libsuf) --endif -- - # ---------------------------------------- - # Special magic for the ghc-prim package - -@@ -581,7 +575,6 @@ BUILD_DIRS += \ +This patch could be replaced by a configure call if +http://hackage.haskell.org/trac/ghc/ticket/5743 were fixed. + +Index: ghc-7.4.0.20111219/ghc.mk +=================================================================== +--- ghc-7.4.0.20111219.orig/ghc.mk 2011-12-21 23:21:03.000000000 +0100 ++++ ghc-7.4.0.20111219/ghc.mk 2011-12-21 23:21:04.000000000 +0100 +@@ -579,7 +579,6 @@ driver/ghci \ driver/ghc \ driver/haddock \ @@ -41,80 +13,40 @@ diff -up ghc-7.0.1/ghc.mk.libffi ghc-7.0.1/ghc.mk includes \ rts -@@ -937,11 +930,10 @@ INSTALL_DISTDIR_compiler = stage2 - - # Now we can do the installation - install_packages: install_libexecs --install_packages: libffi/package.conf.install rts/package.conf.install -+install_packages: rts/package.conf.install - $(call INSTALL_DIR,"$(DESTDIR)$(topdir)") - "$(RM)" $(RM_OPTS_REC) "$(INSTALLED_PACKAGE_CONF)" - $(call INSTALL_DIR,"$(INSTALLED_PACKAGE_CONF)") -- "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update libffi/package.conf.install - "$(INSTALLED_GHC_PKG_REAL)" --force --global-conf "$(INSTALLED_PACKAGE_CONF)" update rts/package.conf.install - $(foreach p, $(INSTALLED_PKG_DIRS), \ - $(call make-command, \ -@@ -1024,7 +1016,7 @@ BIN_DIST_MK = $(BIN_DIST_PREP_DIR)/bindi - unix-binary-dist-prep: - "$(RM)" $(RM_OPTS_REC) bindistprep/ - "$(MKDIRHIER)" $(BIN_DIST_PREP_DIR) -- set -e; for i in packages LICENSE compiler ghc rts libraries utils docs libffi includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done -+ set -e; for i in packages LICENSE compiler ghc rts libraries utils docs includes driver mk rules Makefile aclocal.m4 config.sub config.guess install-sh extra-gcc-opts.in ghc.mk inplace distrib/configure.ac distrib/README distrib/INSTALL; do ln -s ../../$$i $(BIN_DIST_PREP_DIR)/; done - echo "HADDOCK_DOCS = $(HADDOCK_DOCS)" >> $(BIN_DIST_MK) - echo "LATEX_DOCS = $(LATEX_DOCS)" >> $(BIN_DIST_MK) - echo "BUILD_DOCBOOK_HTML = $(BUILD_DOCBOOK_HTML)" >> $(BIN_DIST_MK) -@@ -1102,7 +1094,7 @@ SRC_DIST_DIR=$(shell pwd)/$(SRC_DIST_NAM - # - # Files to include in source distributions - # --SRC_DIST_DIRS = mk rules docs distrib bindisttest libffi includes utils docs rts compiler ghc driver libraries ghc-tarballs -+SRC_DIST_DIRS = mk rules docs distrib bindisttest includes utils docs rts compiler ghc driver libraries ghc-tarballs - SRC_DIST_FILES += \ - configure.ac config.guess config.sub configure \ - aclocal.m4 README ANNOUNCE HACKING LICENSE Makefile install-sh \ -diff -up ghc-7.0.1/rts/ghc.mk.libffi ghc-7.0.1/rts/ghc.mk ---- ghc-7.0.1/rts/ghc.mk.libffi 2010-11-13 04:10:06.000000000 +1000 -+++ ghc-7.0.1/rts/ghc.mk 2010-11-16 19:06:09.000000000 +1000 -@@ -430,15 +430,15 @@ endif - - $(eval $(call build-dependencies,rts,dist,1)) - --$(rts_dist_depfile_c_asm) : libffi/dist-install/build/ffi.h $(DTRACEPROBES_H) -+$(rts_dist_depfile_c_asm) : $(DTRACEPROBES_H) - - #----------------------------------------------------------------------------- - # libffi stuff - --rts_CC_OPTS += -Ilibffi/build/include --rts_HC_OPTS += -Ilibffi/build/include --rts_HSC2HS_OPTS += -Ilibffi/build/include --rts_LD_OPTS += -Llibffi/build/include -+rts_CC_OPTS += $(shell pkg-config --cflags libffi) -+rts_HC_OPTS += $(shell pkg-config --cflags libffi) -+rts_HSC2HS_OPTS += $(shell pkg-config --cflags libffi) -+rts_LD_OPTS += $(shell pkg-config --libs libffi) +Index: ghc-7.4.0.20111219/rts/ghc.mk +=================================================================== +--- ghc-7.4.0.20111219.orig/rts/ghc.mk 2011-12-21 19:56:29.000000000 +0100 ++++ ghc-7.4.0.20111219/rts/ghc.mk 2011-12-21 23:23:52.000000000 +0100 +@@ -177,7 +176,7 @@ + "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ + -no-auto-link-packages -Lrts/dist/build -lffi-5 `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ + else +-$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend rts/dist/build/libffi$$(soext) ++$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend + "$$(RM)" $$(RM_OPTS) $$@ + "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ + -no-auto-link-packages -Lrts/dist/build -lffi `cat rts/libs.depend` $$(rts_$1_OBJS) \ +@@ -188,9 +187,9 @@ + endif + endif + else +-$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) $$(rts_ffi_objs_stamp) ++$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) + "$$(RM)" $$(RM_OPTS) $$@ +- echo $$(rts_ffi_objs) $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ ++ echo $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ + $$(AR_OPTS_STAGE1) $$(EXTRA_AR_ARGS_STAGE1) $$@ + endif - # ----------------------------------------------------------------------------- - # compile dtrace probes if dtrace is supported -diff -up ghc-7.0.1/rts/package.conf.in.libffi ghc-7.0.1/rts/package.conf.in ---- ghc-7.0.1/rts/package.conf.in.libffi 2010-11-13 04:10:06.000000000 +1000 -+++ ghc-7.0.1/rts/package.conf.in 2010-11-16 19:04:28.000000000 +1000 -@@ -24,8 +24,9 @@ library-dirs: TOP"/rts/dist/build" PAPI - hs-libraries: "HSrts" +@@ -504,10 +503,8 @@ + # installing - extra-libraries: -+ "ffi" - #ifdef HAVE_LIBM -- "m" /* for ldexp() */ -+ , "m" /* for ldexp() */ - #endif - #ifdef HAVE_LIBRT - , "rt" -@@ -55,7 +56,6 @@ include-dirs: TOP"/includes" - #endif + INSTALL_LIBS += $(ALL_RTS_LIBS) +-INSTALL_LIBS += $(wildcard rts/dist/build/libffi$(soext)*) +-INSTALL_LIBS += $(wildcard rts/dist/build/libffi-5.dll) - includes: Stg.h --depends: builtin_ffi - hugs-options: - cc-options: +-install: install_libffi_headers ++install: + .PHONY: install_libffi_headers + install_libffi_headers : diff --git a/ghc.spec b/ghc.spec index 12d56c3..2b6c180 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,8 +2,8 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} #%%global without_hscolour 1 # To do a test build instead with shared libs, uncomment the following: @@ -24,12 +24,12 @@ Name: ghc # part of haskell-platform # NB make sure to rebuild ghc after a version bump to avoid ABI change problems -Version: 7.0.4 +Version: 7.4.1 # Since library subpackages are versioned: # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 42%{?dist} +Release: 1%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel @@ -38,7 +38,7 @@ License: %BSDHaskellReport Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} -Source2: http://www.haskell.org/ghc/dist/%{version}/testsuite-%{version}.tar.bz2 +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ @@ -68,6 +68,9 @@ BuildRequires: python %ifarch ppc64 BuildRequires: autoconf %endif +%ifarch armv7hl armv5tel +BuildRequires: llvm >= 3.0 +%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} @@ -77,11 +80,11 @@ Patch3: ghc-gen_contents_index-cron-batch.patch Patch4: ghc-use-system-libffi.patch # add cabal configure option --enable-executable-dynamic # (see http://hackage.haskell.org/trac/hackage/ticket/600) -Patch5: Cabal-option-executable-dynamic.patch -Patch6: ghc-fix-linking-on-sparc.patch Patch7: ghc-ppc64-pthread.patch # http://hackage.haskell.org/trac/ghc/ticket/4999 Patch8: ghc-powerpc-linker-mmap.patch +# fix dynamic linking of executables using Template Haskell +Patch9: Cabal-fix-dynamic-exec-for-TH.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -132,29 +135,31 @@ To install all of ghc, install the ghc base package. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_binlib_package Cabal 1.10.2.0 -%ghc_binlib_package -l %BSDHaskellReport array 0.3.0.2 -%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel,libffi-devel base 4.3.1.0 -%ghc_binlib_package bytestring 0.9.1.10 -%ghc_binlib_package -l %BSDHaskellReport containers 0.4.0.0 -%ghc_binlib_package -l %BSDHaskellReport directory 1.1.0.0 -%ghc_binlib_package -l %BSDHaskellReport extensible-exceptions 0.1.1.2 -%ghc_binlib_package filepath 1.2.0.0 +%ghc_binlib_package Cabal 1.14.0 +%ghc_binlib_package -l %BSDHaskellReport array 0.4.0.0 +%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel,libffi-devel base 4.5.0.0 +%ghc_binlib_package binary 0.5.1.0 +%ghc_binlib_package bytestring 0.9.2.1 +%ghc_binlib_package -l %BSDHaskellReport containers 0.4.2.1 +%ghc_binlib_package -l %BSDHaskellReport deepseq 1.3.0.0 +%ghc_binlib_package -l %BSDHaskellReport directory 1.1.0.2 +%ghc_binlib_package -l %BSDHaskellReport extensible-exceptions 0.1.1.4 +%ghc_binlib_package filepath 1.3.0.0 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_binlib_package -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_binlib_package -l HaskellReport haskell2010 1.0.0.0 -%ghc_binlib_package -l HaskellReport haskell98 1.1.0.1 -%ghc_binlib_package hpc 0.5.0.6 -%ghc_binlib_package -l %BSDHaskellReport old-locale 1.0.0.2 -%ghc_binlib_package -l %BSDHaskellReport old-time 1.0.0.6 -%ghc_binlib_package pretty 1.0.1.2 -%ghc_binlib_package -l %BSDHaskellReport process 1.0.1.5 -%ghc_binlib_package -l %BSDHaskellReport random 1.0.0.3 -%ghc_binlib_package template-haskell 2.5.0.0 -%ghc_binlib_package time 1.2.0.3 -%ghc_binlib_package unix 2.4.2.0 +%ghc_binlib_package -l HaskellReport haskell2010 1.1.0.1 +%ghc_binlib_package -l HaskellReport haskell98 2.0.0.1 +%ghc_binlib_package hoopl 3.8.7.3 +%ghc_binlib_package hpc 0.5.1.1 +%ghc_binlib_package -l %BSDHaskellReport old-locale 1.0.0.4 +%ghc_binlib_package -l %BSDHaskellReport old-time 1.1.0.0 +%ghc_binlib_package pretty 1.1.1.0 +%ghc_binlib_package -l %BSDHaskellReport process 1.1.0.1 +%ghc_binlib_package template-haskell 2.7.0.0 +%ghc_binlib_package time 1.4 +%ghc_binlib_package unix 2.5.1.0 %endif %global version %{ghc_version_override} @@ -191,10 +196,6 @@ rm -r ghc-tarballs/{mingw,perl} %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi -%patch5 -p1 -b .orig - -%patch6 -p1 -b .sparclinking - %ifarch ppc64 %patch7 -p1 -b .pthread %endif @@ -203,6 +204,8 @@ rm -r ghc-tarballs/libffi %patch8 -p1 -b .mmap %endif +%patch9 -p1 -b .orig + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms @@ -257,9 +260,8 @@ done %ghc_gen_filelists bin-package-db 0.0.0.0 %ghc_gen_filelists ghc %{ghc_version_override} -%ghc_gen_filelists ghc-binary 0.5.0.2 %ghc_gen_filelists ghc-prim 0.2.0.0 -%ghc_gen_filelists integer-gmp 0.2.0.3 +%ghc_gen_filelists integer-gmp 0.4.0.0 %define merge_filelist()\ %if %{undefined ghc_without_shared}\ @@ -271,7 +273,6 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base -%merge_filelist ghc-binary ghc %merge_filelist bin-package-db ghc %if %{undefined ghc_without_shared} @@ -321,7 +322,7 @@ inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic rm testghc/* %endif %if %{undefined without_testsuite} -make -C testsuite/tests/ghc-regress fast +make test %endif %post compiler @@ -366,11 +367,9 @@ fi %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc %dir %{ghclibdir} -%{ghclibdir}/extra-gcc-opts %{ghclibdir}/ghc %{ghclibdir}/ghc-pkg %ifnarch %{unregisterised_archs} -%{ghclibdir}/ghc-asm %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt @@ -379,6 +378,7 @@ fi %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/runghc +%{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit %{_mandir}/man1/ghc.* @@ -415,6 +415,19 @@ fi %files libraries %changelog +* Wed Feb 15 2012 Jens Petersen - 7.4.1-1 +- update to new 7.4.1 major release + http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/release-7-4-1.html +- all library versions bumped +- binary package replaces ghc-binary +- random library dropped +- new hoopl library +- deepseq is now included in ghc +- Cabal --enable-executable-dynamic patch is upstream +- add Cabal-fix-dynamic-exec-for-TH.patch +- sparc linking fix is upstream +- setup ghc-deps.sh after ghc_version_override for bootstrapping + * Thu Jan 19 2012 Jens Petersen - 7.0.4-42 - move ghc-ghc-devel from ghc-libraries to the ghc metapackage diff --git a/sources b/sources index 5c31c12..1013c18 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -f167b0b4538d1a56788f43fcc662b568 ghc-7.0.4-src.tar.bz2 -1680925a557821d7e3abab368f37fbdc testsuite-7.0.4.tar.bz2 +54bc9405c14c3226b6e3de3cd61e2777 ghc-7.4.1-testsuite.tar.bz2 +5d86c420978b49cc60edea9bd4c36703 ghc-7.4.1-src.tar.bz2 From 6905835f80812915b8b8fe289d0b28b2213836ef Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Feb 2012 15:16:20 +0900 Subject: [PATCH 305/530] fix build with system libffi - add rest of debian system-libffi patch, - copy libffi headers into rts build dir - acknowledge Debian's patch --- ghc-use-system-libffi.patch | 33 ++++++++++++++++++++++++++++++++- ghc.spec | 3 +++ 2 files changed, 35 insertions(+), 1 deletion(-) diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index cac9e42..304bcb9 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -1,6 +1,21 @@ This patch could be replaced by a configure call if http://hackage.haskell.org/trac/ghc/ticket/5743 were fixed. +Index: ghc-7.4.0.20111219/rts/package.conf.in +=================================================================== +--- ghc-7.4.0.20111219.orig/rts/package.conf.in 2011-12-21 23:21:03.000000000 +0100 ++++ ghc-7.4.0.20111219/rts/package.conf.in 2011-12-21 23:21:04.000000000 +0100 +@@ -24,8 +24,9 @@ + hs-libraries: "HSrts" + + extra-libraries: ++ "ffi" + #ifdef HAVE_LIBM +- "m" /* for ldexp() */ ++ , "m" /* for ldexp() */ + #endif + #ifdef HAVE_LIBRT + , "rt" Index: ghc-7.4.0.20111219/ghc.mk =================================================================== --- ghc-7.4.0.20111219.orig/ghc.mk 2011-12-21 23:21:03.000000000 +0100 @@ -17,7 +32,23 @@ Index: ghc-7.4.0.20111219/rts/ghc.mk =================================================================== --- ghc-7.4.0.20111219.orig/rts/ghc.mk 2011-12-21 19:56:29.000000000 +0100 +++ ghc-7.4.0.20111219/rts/ghc.mk 2011-12-21 23:23:52.000000000 +0100 -@@ -177,7 +176,7 @@ +@@ -86,8 +86,7 @@ + ALL_RTS_DEF_LIBNAMES = base ghc-prim + ALL_RTS_DEF_LIBS = \ + rts/dist/build/win32/libHSbase.dll.a \ +- rts/dist/build/win32/libHSghc-prim.dll.a \ +- libffi/build/inst/lib/libffi.dll.a ++ rts/dist/build/win32/libHSghc-prim.dll.a + + # -- import libs for the regular Haskell libraries + define make-importlib-def # args $1 = lib name +@@ -172,12 +171,12 @@ + # Making a shared library for the RTS. + ifneq "$$(findstring dyn, $1)" "" + ifeq "$$(HOSTPLATFORM)" "i386-unknown-mingw32" +-$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/libffi-5.dll ++$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend + "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ -no-auto-link-packages -Lrts/dist/build -lffi-5 `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ else diff --git a/ghc.spec b/ghc.spec index 2b6c180..a9d496e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -195,6 +195,8 @@ rm -r ghc-tarballs/{mingw,perl} # use system libffi %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi +mkdir -p rts/dist/build +cp $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %ifarch ppc64 %patch7 -p1 -b .pthread @@ -426,6 +428,7 @@ fi - Cabal --enable-executable-dynamic patch is upstream - add Cabal-fix-dynamic-exec-for-TH.patch - sparc linking fix is upstream +- uses Debian's system-libffi patch by Joachim Breitner - setup ghc-deps.sh after ghc_version_override for bootstrapping * Thu Jan 19 2012 Jens Petersen - 7.0.4-42 From 7d87f9af5cf0c3ec3444e8dd7bb791465b6a06c2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 19 Feb 2012 15:57:17 +0900 Subject: [PATCH 306/530] minor ghc.spec cleanup - add another #%%global without_testsuite 1 - make versioned ghc-compiler BR conditional on no ghc_bootstrapping - reformat library BRs - symlink to system libffi headers --- ghc.spec | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index a9d496e..39807e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -5,6 +5,7 @@ %global ghc_bootstrapping 1 %{?ghc_bootstrap} #%%global without_hscolour 1 +#%%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -49,11 +50,18 @@ Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-pa Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 -# change to ghc-compiler once backported to el6 -BuildRequires: ghc %{!?ghc_bootstrapping: = %{version}} +%if %{undefined ghc_bootstrapping} +BuildRequires: ghc-compiler = %{version} +%endif BuildRequires: ghc-rpm-macros >= 0.14 -BuildRequires: gmp-devel, libffi-devel -BuildRequires: ghc-directory-devel, ghc-process-devel, ghc-pretty-devel, ghc-containers-devel, ghc-haskell98-devel, ghc-bytestring-devel +BuildRequires: ghc-bytestring-devel +BuildRequires: ghc-containers-devel +BuildRequires: ghc-directory-devel +BuildRequires: ghc-haskell98-devel +BuildRequires: ghc-pretty-devel +BuildRequires: ghc-process-devel +BuildRequires: gmp-devel +BuildRequires: libffi-devel # for internal terminfo BuildRequires: ncurses-devel %if %{undefined without_manual} @@ -196,7 +204,7 @@ rm -r ghc-tarballs/{mingw,perl} %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi mkdir -p rts/dist/build -cp $(pkg-config --variable=includedir libffi)/*.h rts/dist/build +ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %ifarch ppc64 %patch7 -p1 -b .pthread From 10ede6d8ab1cec854310938303e9b760de4784d7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Feb 2012 11:16:14 +0900 Subject: [PATCH 307/530] add %_isa to external dependencies --- ghc.spec | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 39807e2..76e626a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -4,8 +4,8 @@ # To bootstrap a new version of ghc, uncomment the following: %global ghc_bootstrapping 1 %{?ghc_bootstrap} -#%%global without_hscolour 1 -#%%global without_testsuite 1 +%global without_hscolour 1 +%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -118,8 +118,8 @@ for the functional language Haskell. Highlights: Summary: GHC compiler and utilities License: BSD Group: Development/Languages -Requires: gcc -Requires: ghc-base-devel +Requires: gcc%{?_isa} +Requires: ghc-base-devel%{?_isa} Requires(post): chkconfig Requires(postun): chkconfig # added in f14 @@ -145,7 +145,7 @@ To install all of ghc, install the ghc base package. %if %{defined ghclibdir} %ghc_binlib_package Cabal 1.14.0 %ghc_binlib_package -l %BSDHaskellReport array 0.4.0.0 -%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel,libffi-devel base 4.5.0.0 +%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.0.0 %ghc_binlib_package binary 0.5.1.0 %ghc_binlib_package bytestring 0.9.2.1 %ghc_binlib_package -l %BSDHaskellReport containers 0.4.2.1 From ee30456e2b8c5a9eddc3312e8b8eb62ed3edf1cf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Feb 2012 11:17:31 +0900 Subject: [PATCH 308/530] try temporarily disabling all the ppc64 "hacks" to see if really all needed --- ghc.spec | 19 ------------------- 1 file changed, 19 deletions(-) diff --git a/ghc.spec b/ghc.spec index 76e626a..8cce7fe 100644 --- a/ghc.spec +++ b/ghc.spec @@ -73,9 +73,6 @@ BuildRequires: hscolour %if %{undefined without_testsuite} BuildRequires: python %endif -%ifarch ppc64 -BuildRequires: autoconf -%endif %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif @@ -206,14 +203,6 @@ rm -r ghc-tarballs/libffi mkdir -p rts/dist/build ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build -%ifarch ppc64 -%patch7 -p1 -b .pthread -%endif - -%ifarch ppc ppc64 -%patch8 -p1 -b .mmap -%endif - %patch9 -p1 -b .orig @@ -234,16 +223,8 @@ HSCOLOUR_SRCS = NO %ifarch %{unregisterised_archs} GhcUnregisterised=YES %endif -%ifarch ppc64 -GhcNotThreaded=YES -SRC_HC_OPTS+=-optc-mminimal-toc -optl-pthread -SRC_CC_OPTS+=-mminimal-toc -pthread -Wa,--noexecstack -%endif EOF -%ifarch ppc64 -autoreconf -%endif export CFLAGS="${CFLAGS:-%optflags}" # specify gcc to avoid problems when bootstrapping with ccache ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ From c0f89535cdf26ee3b3b48969270d863a4ba53fcf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Feb 2012 11:27:37 +0900 Subject: [PATCH 309/530] tweak release for test scm build --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8cce7fe..f233b1d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 1%{?dist} +Release: 0.1%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on the following archs: #ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel From 6130e65e949fc8d68bfcea1e69d67f4f922b0630 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 21 Mar 2012 19:05:22 +0900 Subject: [PATCH 310/530] major update to ghc-7.4.1 - http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/release-7-4-1.html - add Cabal-fix-dynamic-exec-for-TH.patch - use Debian's system-libffi patch - drop ppc64 config, pthread and mmap patches - add s390 and s390x to unregisterised_archs --- ...pthread.patch => ghc-powerpc-pthread.patch | 0 ghc.spec | 36 +++++++++++-------- 2 files changed, 21 insertions(+), 15 deletions(-) rename ghc-ppc64-pthread.patch => ghc-powerpc-pthread.patch (100%) diff --git a/ghc-ppc64-pthread.patch b/ghc-powerpc-pthread.patch similarity index 100% rename from ghc-ppc64-pthread.patch rename to ghc-powerpc-pthread.patch diff --git a/ghc.spec b/ghc.spec index f233b1d..d6d12f2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,7 +14,7 @@ #%%global without_testsuite 1 # unregisterized archs -%global unregisterised_archs ppc64 armv7hl armv5tel +%global unregisterised_archs ppc64 armv7hl armv5tel s390 s390x # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} @@ -30,11 +30,12 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 0.1%{?dist} +Release: 1%{?dist} Summary: Glasgow Haskell Compiler -# fedora ghc has been bootstrapped on the following archs: -#ExclusiveArch: %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel -ExcludeArch: sparc64 s390x +# fedora ghc has been bootstrapped on +# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x +# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros +ExcludeArch: sparc64 License: %BSDHaskellReport Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 @@ -79,13 +80,17 @@ BuildRequires: llvm >= 3.0 Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} +# absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch +# type-level too big so skip it in gen_contents_index Patch2: ghc-gen_contents_index-type-level.patch +# disable gen_contents_index when not --batch for cron Patch3: ghc-gen_contents_index-cron-batch.patch +# fedora does not allow copy libraries Patch4: ghc-use-system-libffi.patch # add cabal configure option --enable-executable-dynamic # (see http://hackage.haskell.org/trac/hackage/ticket/600) -Patch7: ghc-ppc64-pthread.patch +Patch7: ghc-powerpc-pthread.patch # http://hackage.haskell.org/trac/ghc/ticket/4999 Patch8: ghc-powerpc-linker-mmap.patch # fix dynamic linking of executables using Template Haskell @@ -188,11 +193,8 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} -# absolute haddock path (was for html/libraries -> libraries) %patch1 -p1 -b .orig -# type-level too big so skip it in gen_contents_index %patch2 -p1 -# disable gen_contents_index when not --batch for cron %patch3 -p1 # make sure we don't use these @@ -205,7 +207,6 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch9 -p1 -b .orig - %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -220,8 +221,9 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif +## should be unnecessary %ifarch %{unregisterised_archs} -GhcUnregisterised=YES +#GhcUnregisterised=YES %endif EOF @@ -372,7 +374,6 @@ fi %{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit -%{_mandir}/man1/ghc.* %dir %{_docdir}/ghc %dir %{ghcdocbasedir} %if %{undefined without_haddock} @@ -381,9 +382,10 @@ fi %{ghclibdir}/haddock %{ghclibdir}/html %{ghclibdir}/latex -%{ghcdocbasedir}/html %if %{undefined without_manual} -%{ghcdocbasedir}/Cabal +%{_mandir}/man1/ghc.* +## needs pandoc +#%{ghcdocbasedir}/Cabal %{ghcdocbasedir}/haddock %{ghcdocbasedir}/users_guide %endif @@ -417,8 +419,12 @@ fi - Cabal --enable-executable-dynamic patch is upstream - add Cabal-fix-dynamic-exec-for-TH.patch - sparc linking fix is upstream -- uses Debian's system-libffi patch by Joachim Breitner +- use Debian's system-libffi patch by Joachim Breitner - setup ghc-deps.sh after ghc_version_override for bootstrapping +- drop ppc64 config, pthread and mmap patches +- do not set GhcUnregisterised explicitly +- add s390 and s390x to unregisterised_archs +- Cabal manual needs pandoc * Thu Jan 19 2012 Jens Petersen - 7.0.4-42 - move ghc-ghc-devel from ghc-libraries to the ghc metapackage From 0da60f05cbb34fb10b70a21d7e1a58799e65a813 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 21 Mar 2012 19:36:26 +0900 Subject: [PATCH 311/530] move ghc manpage out of without_manual in filelist --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d6d12f2..4f0452f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -374,6 +374,7 @@ fi %{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit +%{_mandir}/man1/ghc.* %dir %{_docdir}/ghc %dir %{ghcdocbasedir} %if %{undefined without_haddock} @@ -383,7 +384,6 @@ fi %{ghclibdir}/html %{ghclibdir}/latex %if %{undefined without_manual} -%{_mandir}/man1/ghc.* ## needs pandoc #%{ghcdocbasedir}/Cabal %{ghcdocbasedir}/haddock From a3513a1d65b377b62b4518a1d9cdadf23875536a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 21 Mar 2012 20:49:32 +0900 Subject: [PATCH 312/530] turn off bootstrapping options for full build --- ghc.spec | 13 ++++++++----- 1 file changed, 8 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4f0452f..5133fb8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_hscolour 1 -%global without_testsuite 1 +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_hscolour 1 +#%%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 1%{?dist} +Release: 2%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -408,6 +408,9 @@ fi %files libraries %changelog +* Wed Mar 21 2012 Jens Petersen - 7.4.1-2 +- full build + * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 - update to new 7.4.1 major release http://www.haskell.org/ghc/docs/7.4.1/html/users_guide/release-7-4-1.html From bc252ac183aefe56f6cbc08d3c1de00c47cb281e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 10 Apr 2012 11:20:14 +0900 Subject: [PATCH 313/530] BR clang not just llvm for ARM; bootstrap build --- ghc.spec | 17 +++++++++-------- 1 file changed, 9 insertions(+), 8 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5133fb8..40060b6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_hscolour 1 -#%%global without_testsuite 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_hscolour 1 +%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 2%{?dist} +Release: 1.1%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -75,7 +75,7 @@ BuildRequires: hscolour BuildRequires: python %endif %ifarch armv7hl armv5tel -BuildRequires: llvm >= 3.0 +BuildRequires: clang >= 3.0 %endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} @@ -408,8 +408,9 @@ fi %files libraries %changelog -* Wed Mar 21 2012 Jens Petersen - 7.4.1-2 -- full build +* Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 +- BR clang not just llvm for ARM +- bootstrap build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 - update to new 7.4.1 major release From a357d572f79e80d4696e5bacde04d6af6a45ba20 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 13 Apr 2012 23:27:46 +0900 Subject: [PATCH 314/530] drop --with-gcc --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 40060b6..c62c3ee 100644 --- a/ghc.spec +++ b/ghc.spec @@ -228,13 +228,12 @@ HSCOLOUR_SRCS = NO EOF export CFLAGS="${CFLAGS:-%optflags}" -# specify gcc to avoid problems when bootstrapping with ccache +# use --with-gcc=%{_bindir}/gcc when bootstrapping to avoid ccache hardcoding problem ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} # >4 cpus tends to break build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(%{_bindir}/getconf _NPROCESSORS_ONLN) @@ -410,6 +409,7 @@ fi %changelog * Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 - BR clang not just llvm for ARM +- drop --with-gcc - bootstrap build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 From ab8589c9becca77b586bc2bb3caa330afb8c69b3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 14 Apr 2012 00:23:08 +0900 Subject: [PATCH 315/530] set CC to clang for ARM --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c62c3ee..5808a2b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -229,6 +229,9 @@ EOF export CFLAGS="${CFLAGS:-%optflags}" # use --with-gcc=%{_bindir}/gcc when bootstrapping to avoid ccache hardcoding problem +%ifarch armv7hl armv5tel +export CC=clang +%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -408,7 +411,7 @@ fi %changelog * Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 -- BR clang not just llvm for ARM +- build with llvm clang on ARM - drop --with-gcc - bootstrap build From 0860e86239edb314cb0168d79817e031618233fe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 14 Apr 2012 01:37:26 +0900 Subject: [PATCH 316/530] add 4 ARM patches from Debian for armel and armhf - BR llvm not clang - remove arm from unregisterised_archs - revert dropping --with-gcc --- ghc.spec | 33 ++++++++++++++++++++++++--------- 1 file changed, 24 insertions(+), 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5808a2b..b8f9df9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,7 +14,7 @@ #%%global without_testsuite 1 # unregisterized archs -%global unregisterised_archs ppc64 armv7hl armv5tel s390 s390x +%global unregisterised_archs ppc64 s390 s390x # ghc does not output dwarf format so debuginfo is not useful %global debug_package %{nil} @@ -75,7 +75,7 @@ BuildRequires: hscolour BuildRequires: python %endif %ifarch armv7hl armv5tel -BuildRequires: clang >= 3.0 +BuildRequires: llvm >= 3.0 %endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} @@ -95,6 +95,12 @@ Patch7: ghc-powerpc-pthread.patch Patch8: ghc-powerpc-linker-mmap.patch # fix dynamic linking of executables using Template Haskell Patch9: Cabal-fix-dynamic-exec-for-TH.patch +# Debian armel fixes +Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch +Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch +# Debian armhf fixes +Patch12: ghc-debian-ARM-VFPv3D16.patch +Patch13: ghc-debian-armhf_llvm_abi.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -126,7 +132,9 @@ Requires(post): chkconfig Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 -# llvm is an optional dependency +%ifarch armv7hl armv5tel +Requires: llvm >= 3.0 +%endif %description compiler The package contains the GHC compiler, tools and utilities. @@ -207,6 +215,14 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch9 -p1 -b .orig +# ARM patches +%ifarch armv7hl armv5tel +%patch10 -p0 -b .arm1 +%patch11 -p0 -b .arm2 +%patch12 -p1 -b .arm +%patch13 -p1 -b .arm +%endif + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -229,14 +245,12 @@ EOF export CFLAGS="${CFLAGS:-%optflags}" # use --with-gcc=%{_bindir}/gcc when bootstrapping to avoid ccache hardcoding problem -%ifarch armv7hl armv5tel -export CC=clang -%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ - --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} + --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ + --with-gcc=%{_bindir}/gcc # >4 cpus tends to break build [ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(%{_bindir}/getconf _NPROCESSORS_ONLN) @@ -411,8 +425,9 @@ fi %changelog * Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 -- build with llvm clang on ARM -- drop --with-gcc +- build with llvm-3.0 on ARM +- remove arm from unregisterised_archs +- add 4 Debian ARM patches for armel and armhf (Iain Lane) - bootstrap build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 From 4219642675961ea054921dac0bc6ef5979210dc5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 14 Apr 2012 01:46:47 +0900 Subject: [PATCH 317/530] add the new debian ARM patches --- ...to-not-save-and-restore-r11-fp-regis.patch | 29 ++++++++++++++++ ...n-clobbered-register-list-for-both-A.patch | 34 +++++++++++++++++++ ghc-debian-ARM-VFPv3D16.patch | 16 +++++++++ ghc-debian-armhf_llvm_abi.patch | 26 ++++++++++++++ 4 files changed, 105 insertions(+) create mode 100644 fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch create mode 100644 fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch create mode 100644 ghc-debian-ARM-VFPv3D16.patch create mode 100644 ghc-debian-armhf_llvm_abi.patch diff --git a/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch b/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch new file mode 100644 index 0000000..98772f1 --- /dev/null +++ b/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch @@ -0,0 +1,29 @@ +From 1cbf3bcae87dd102942d85ce71ea17d42d4b5f5a Mon Sep 17 00:00:00 2001 +From: Karel Gardas +Date: Tue, 14 Feb 2012 08:03:07 +0100 +Subject: [PATCH 2/2] fix ARM StgCRun to not save and restore r11/fp register twice + +--- + rts/StgCRun.c | 4 ++-- + 1 files changed, 2 insertions(+), 2 deletions(-) + +--- a/rts/StgCRun.c ++++ b/rts/StgCRun.c +@@ -632,7 +632,7 @@ + /* + * save callee-saves registers on behalf of the STG code. + */ +- "stmfd sp!, {r4-r11, fp, ip, lr}\n\t" ++ "stmfd sp!, {r4-r10, fp, ip, lr}\n\t" + #if !defined(arm_HOST_ARCH_PRE_ARMv6) + "vstmdb sp!, {d8-d11}\n\t" + #endif +@@ -669,7 +669,7 @@ + #if !defined(arm_HOST_ARCH_PRE_ARMv6) + "vldmia sp!, {d8-d11}\n\t" + #endif +- "ldmfd sp!, {r4-r11, fp, ip, lr}\n\t" ++ "ldmfd sp!, {r4-r10, fp, ip, lr}\n\t" + : "=r" (r) + : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) + #if !defined(__thumb__) diff --git a/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch b/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch new file mode 100644 index 0000000..f033c18 --- /dev/null +++ b/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch @@ -0,0 +1,34 @@ +From 957f778cb971d63cbbea0c71c727c94474b1b905 Mon Sep 17 00:00:00 2001 +From: Karel Gardas +Date: Tue, 14 Feb 2012 08:01:47 +0100 +Subject: [PATCH 1/2] fix ARM's StgCRun clobbered register list for both ARM and Thumb modes + +--- + rts/StgCRun.c | 16 +++++++++++++++- + 1 files changed, 15 insertions(+), 1 deletions(-) + +--- a/rts/StgCRun.c ++++ b/rts/StgCRun.c +@@ -672,7 +672,21 @@ + "ldmfd sp!, {r4-r11, fp, ip, lr}\n\t" + : "=r" (r) + : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) +- : "%r4", "%r5", "%r6", "%r8", "%r9", "%r10", "%r11", "%fp", "%ip", "%lr" ++#if !defined(__thumb__) ++ /* In ARM mode, r11/fp is frame-pointer and so we cannot mark ++ it as clobbered. If we do so, GCC complains with error. */ ++ : "%r4", "%r5", "%r6", "%r7", "%r8", "%r9", "%r10", "%ip", "%lr" ++#else ++ /* In Thumb mode r7 is frame-pointer and so we cannot mark it ++ as clobbered. On the other hand we mark as clobbered also ++ those regs not used in Thumb mode. Hard to judge if this is ++ needed, but certainly Haskell code is using them for ++ placing GHC's virtual registers there. See ++ includes/stg/MachRegs.h Please note that Haskell code is ++ compiled by GHC/LLVM into ARM code (not Thumb!), at least ++ as of February 2012 */ ++ : "%r4", "%r5", "%r6", "%r8", "%r9", "%r10", "%fp", "%ip", "%lr" ++#endif + ); + return r; + } diff --git a/ghc-debian-ARM-VFPv3D16.patch b/ghc-debian-ARM-VFPv3D16.patch new file mode 100644 index 0000000..ffe76cb --- /dev/null +++ b/ghc-debian-ARM-VFPv3D16.patch @@ -0,0 +1,16 @@ +Description: Use VFPv3-D16 FPU for ARM builds +Author: Jani Monoses + +Index: ghc/aclocal.m4 +=================================================================== +--- ghc.orig/aclocal.m4 2012-02-01 18:10:32.000000000 +0000 ++++ ghc/aclocal.m4 2012-03-10 16:40:32.415005650 +0000 +@@ -333,7 +333,7 @@ + ], + [changequote(, )dnl + ARM_ISA=ARMv7 +- ARM_ISA_EXT="[VFPv3,NEON]" ++ ARM_ISA_EXT="[VFPv3D16,NEON]" + changequote([, ])dnl + ]) + ]) diff --git a/ghc-debian-armhf_llvm_abi.patch b/ghc-debian-armhf_llvm_abi.patch new file mode 100644 index 0000000..c3b045e --- /dev/null +++ b/ghc-debian-armhf_llvm_abi.patch @@ -0,0 +1,26 @@ +Description: If we are on armhf, tell llvm to generate code for this ABI. Not + forwarded upstream, because they will do a more 'proper' patch. See upstream + bug #5914. +Author: Iain Lane + +Index: ghc/compiler/main/DriverPipeline.hs +=================================================================== +--- ghc.orig/compiler/main/DriverPipeline.hs 2012-03-10 16:41:46.000000000 +0000 ++++ ghc/compiler/main/DriverPipeline.hs 2012-03-10 16:42:59.209169474 +0000 +@@ -1,5 +1,5 @@ + {-# OPTIONS -fno-cse #-} +-{-# LANGUAGE NamedFieldPuns #-} ++{-# LANGUAGE NamedFieldPuns, CPP #-} + -- -fno-cse is needed for GLOBAL_VAR's to behave properly + + ----------------------------------------------------------------------------- +@@ -1379,6 +1379,9 @@ + then ["-mattr=+v7,+vfp3"] + else if (elem VFPv3D16 ext) + then ["-mattr=+v7,+vfp3,+d16"] ++#ifdef __ARM_PCS_VFP ++ ++ ["-float-abi=hard"] ++#endif + else [] + _ -> [] + From c633311f76d8d2acd2d967d55776af53e35a8602 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 14 Apr 2012 02:14:37 +0900 Subject: [PATCH 318/530] the armel patches are -p1 --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index b8f9df9..9c5e356 100644 --- a/ghc.spec +++ b/ghc.spec @@ -217,8 +217,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build # ARM patches %ifarch armv7hl armv5tel -%patch10 -p0 -b .arm1 -%patch11 -p0 -b .arm2 +%patch10 -p1 -b .arm1 +%patch11 -p1 -b .arm2 %patch12 -p1 -b .arm %patch13 -p1 -b .arm %endif From 5a80b53c41a0265b7fa584467bb8ab384e46c8fc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 14 Apr 2012 12:18:52 +0900 Subject: [PATCH 319/530] try disabling debian ARM-VFPv3D16 patch /usr/bin/ld: error: /tmp/ghc24961_0/ghc24961_0.o uses VFP register arguments, libraries/base/dist-install/build/GHC/Event/Clock.o does not --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9c5e356..71e8756 100644 --- a/ghc.spec +++ b/ghc.spec @@ -99,7 +99,7 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch # Debian armhf fixes -Patch12: ghc-debian-ARM-VFPv3D16.patch +#Patch12: ghc-debian-ARM-VFPv3D16.patch Patch13: ghc-debian-armhf_llvm_abi.patch %description @@ -219,7 +219,7 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %ifarch armv7hl armv5tel %patch10 -p1 -b .arm1 %patch11 -p1 -b .arm2 -%patch12 -p1 -b .arm +#%%patch12 -p1 -b .arm %patch13 -p1 -b .arm %endif From cc91b0e4292e49ba5df7bb13c1ca939166d2626d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Apr 2012 17:57:54 +0900 Subject: [PATCH 320/530] revert dropping ghc-debian-ARM-VFPv3D16.patch and define __ARM_PCS_VFP in build.mk --- ghc.spec | 9 ++++----- 1 file changed, 4 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 71e8756..81e5744 100644 --- a/ghc.spec +++ b/ghc.spec @@ -99,7 +99,7 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch # Debian armhf fixes -#Patch12: ghc-debian-ARM-VFPv3D16.patch +Patch12: ghc-debian-ARM-VFPv3D16.patch Patch13: ghc-debian-armhf_llvm_abi.patch %description @@ -219,7 +219,7 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %ifarch armv7hl armv5tel %patch10 -p1 -b .arm1 %patch11 -p1 -b .arm2 -#%%patch12 -p1 -b .arm +%patch12 -p1 -b .arm %patch13 -p1 -b .arm %endif @@ -237,9 +237,8 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif -## should be unnecessary -%ifarch %{unregisterised_archs} -#GhcUnregisterised=YES +%ifarch armv7hl +SRC_HC_OPTS += -D__ARM_PCS_VFP" %endif EOF From e549e39f585345085ff7267d9f5e9bee563d23c5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Apr 2012 19:13:27 +0900 Subject: [PATCH 321/530] remove the erroneous doublequote after -D__ARM_PCS_VFP --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 81e5744..15a4360 100644 --- a/ghc.spec +++ b/ghc.spec @@ -238,7 +238,7 @@ BUILD_DOCBOOK_HTML = NO HSCOLOUR_SRCS = NO %endif %ifarch armv7hl -SRC_HC_OPTS += -D__ARM_PCS_VFP" +SRC_HC_OPTS += -D__ARM_PCS_VFP %endif EOF From 3bf6972c25dbf333ab941ab14847379bec1982e6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Apr 2012 10:56:12 +0900 Subject: [PATCH 322/530] avoid actually running aclocal (for +d16) by using hard float patch closer to Ubuntu -drop the original debian armhf llvm driver patches --- ghc-7.4.1-armv7hl-llc-hard-float.patch | 15 +++++++++++++++ ghc-debian-ARM-VFPv3D16.patch | 16 ---------------- ghc-debian-armhf_llvm_abi.patch | 26 -------------------------- ghc.spec | 12 ++++-------- 4 files changed, 19 insertions(+), 50 deletions(-) create mode 100644 ghc-7.4.1-armv7hl-llc-hard-float.patch delete mode 100644 ghc-debian-ARM-VFPv3D16.patch delete mode 100644 ghc-debian-armhf_llvm_abi.patch diff --git a/ghc-7.4.1-armv7hl-llc-hard-float.patch b/ghc-7.4.1-armv7hl-llc-hard-float.patch new file mode 100644 index 0000000..ad6c323 --- /dev/null +++ b/ghc-7.4.1-armv7hl-llc-hard-float.patch @@ -0,0 +1,15 @@ +diff -u ghc-7.4.1/compiler/main/DriverPipeline.hs.orig ghc-7.4.1/compiler/main/DriverPipeline.hs +--- ghc-7.4.1/compiler/main/DriverPipeline.hs.orig 2012-02-02 03:10:32.000000000 +0900 ++++ ghc-7.4.1/compiler/main/DriverPipeline.hs 2012-04-27 10:42:53.142111769 +0900 +@@ -1376,9 +1376,9 @@ + -- does not enable VFP by default. Let's do this manually here + fpOpts = case platformArch (targetPlatform dflags) of + ArchARM ARMv7 ext -> if (elem VFPv3 ext) +- then ["-mattr=+v7,+vfp3"] ++ then ["-mattr=+v7,+vfp3", "-float-abi=hard"] + else if (elem VFPv3D16 ext) +- then ["-mattr=+v7,+vfp3,+d16"] ++ then ["-mattr=+v7,+vfp3,+d16", "-float-abi=hard"] + else [] + _ -> [] + diff --git a/ghc-debian-ARM-VFPv3D16.patch b/ghc-debian-ARM-VFPv3D16.patch deleted file mode 100644 index ffe76cb..0000000 --- a/ghc-debian-ARM-VFPv3D16.patch +++ /dev/null @@ -1,16 +0,0 @@ -Description: Use VFPv3-D16 FPU for ARM builds -Author: Jani Monoses - -Index: ghc/aclocal.m4 -=================================================================== ---- ghc.orig/aclocal.m4 2012-02-01 18:10:32.000000000 +0000 -+++ ghc/aclocal.m4 2012-03-10 16:40:32.415005650 +0000 -@@ -333,7 +333,7 @@ - ], - [changequote(, )dnl - ARM_ISA=ARMv7 -- ARM_ISA_EXT="[VFPv3,NEON]" -+ ARM_ISA_EXT="[VFPv3D16,NEON]" - changequote([, ])dnl - ]) - ]) diff --git a/ghc-debian-armhf_llvm_abi.patch b/ghc-debian-armhf_llvm_abi.patch deleted file mode 100644 index c3b045e..0000000 --- a/ghc-debian-armhf_llvm_abi.patch +++ /dev/null @@ -1,26 +0,0 @@ -Description: If we are on armhf, tell llvm to generate code for this ABI. Not - forwarded upstream, because they will do a more 'proper' patch. See upstream - bug #5914. -Author: Iain Lane - -Index: ghc/compiler/main/DriverPipeline.hs -=================================================================== ---- ghc.orig/compiler/main/DriverPipeline.hs 2012-03-10 16:41:46.000000000 +0000 -+++ ghc/compiler/main/DriverPipeline.hs 2012-03-10 16:42:59.209169474 +0000 -@@ -1,5 +1,5 @@ - {-# OPTIONS -fno-cse #-} --{-# LANGUAGE NamedFieldPuns #-} -+{-# LANGUAGE NamedFieldPuns, CPP #-} - -- -fno-cse is needed for GLOBAL_VAR's to behave properly - - ----------------------------------------------------------------------------- -@@ -1379,6 +1379,9 @@ - then ["-mattr=+v7,+vfp3"] - else if (elem VFPv3D16 ext) - then ["-mattr=+v7,+vfp3,+d16"] -+#ifdef __ARM_PCS_VFP -+ ++ ["-float-abi=hard"] -+#endif - else [] - _ -> [] - diff --git a/ghc.spec b/ghc.spec index 15a4360..fe02411 100644 --- a/ghc.spec +++ b/ghc.spec @@ -98,9 +98,8 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch # Debian armel fixes Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch -# Debian armhf fixes -Patch12: ghc-debian-ARM-VFPv3D16.patch -Patch13: ghc-debian-armhf_llvm_abi.patch +# need to tell llc to use hard float on armv7hl +Patch12: ghc-7.4.1-armv7hl-llc-hard-float.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -220,7 +219,6 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch10 -p1 -b .arm1 %patch11 -p1 -b .arm2 %patch12 -p1 -b .arm -%patch13 -p1 -b .arm %endif %build @@ -237,9 +235,6 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif -%ifarch armv7hl -SRC_HC_OPTS += -D__ARM_PCS_VFP -%endif EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -426,7 +421,8 @@ fi * Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 - build with llvm-3.0 on ARM - remove arm from unregisterised_archs -- add 4 Debian ARM patches for armel and armhf (Iain Lane) +- add Debian ARM register patches (Iain Lane) +- make llc use -float-abi=hard on armv7hl (thanks Debian and Ubuntu) - bootstrap build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 From 760efcba7eda8cef812e0fb3802b1a600ff789f3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Apr 2012 23:18:42 +0900 Subject: [PATCH 323/530] Reverting last patch "avoid actually running aclocal (for +d16) by using hard float patch closer to Ubuntu" and run autoreconf --- ghc-7.4.1-armv7hl-llc-hard-float.patch | 15 --------------- ghc-debian-ARM-VFPv3D16.patch | 16 ++++++++++++++++ ghc-debian-armhf_llvm_abi.patch | 26 ++++++++++++++++++++++++++ ghc.spec | 16 ++++++++++++---- 4 files changed, 54 insertions(+), 19 deletions(-) delete mode 100644 ghc-7.4.1-armv7hl-llc-hard-float.patch create mode 100644 ghc-debian-ARM-VFPv3D16.patch create mode 100644 ghc-debian-armhf_llvm_abi.patch diff --git a/ghc-7.4.1-armv7hl-llc-hard-float.patch b/ghc-7.4.1-armv7hl-llc-hard-float.patch deleted file mode 100644 index ad6c323..0000000 --- a/ghc-7.4.1-armv7hl-llc-hard-float.patch +++ /dev/null @@ -1,15 +0,0 @@ -diff -u ghc-7.4.1/compiler/main/DriverPipeline.hs.orig ghc-7.4.1/compiler/main/DriverPipeline.hs ---- ghc-7.4.1/compiler/main/DriverPipeline.hs.orig 2012-02-02 03:10:32.000000000 +0900 -+++ ghc-7.4.1/compiler/main/DriverPipeline.hs 2012-04-27 10:42:53.142111769 +0900 -@@ -1376,9 +1376,9 @@ - -- does not enable VFP by default. Let's do this manually here - fpOpts = case platformArch (targetPlatform dflags) of - ArchARM ARMv7 ext -> if (elem VFPv3 ext) -- then ["-mattr=+v7,+vfp3"] -+ then ["-mattr=+v7,+vfp3", "-float-abi=hard"] - else if (elem VFPv3D16 ext) -- then ["-mattr=+v7,+vfp3,+d16"] -+ then ["-mattr=+v7,+vfp3,+d16", "-float-abi=hard"] - else [] - _ -> [] - diff --git a/ghc-debian-ARM-VFPv3D16.patch b/ghc-debian-ARM-VFPv3D16.patch new file mode 100644 index 0000000..ffe76cb --- /dev/null +++ b/ghc-debian-ARM-VFPv3D16.patch @@ -0,0 +1,16 @@ +Description: Use VFPv3-D16 FPU for ARM builds +Author: Jani Monoses + +Index: ghc/aclocal.m4 +=================================================================== +--- ghc.orig/aclocal.m4 2012-02-01 18:10:32.000000000 +0000 ++++ ghc/aclocal.m4 2012-03-10 16:40:32.415005650 +0000 +@@ -333,7 +333,7 @@ + ], + [changequote(, )dnl + ARM_ISA=ARMv7 +- ARM_ISA_EXT="[VFPv3,NEON]" ++ ARM_ISA_EXT="[VFPv3D16,NEON]" + changequote([, ])dnl + ]) + ]) diff --git a/ghc-debian-armhf_llvm_abi.patch b/ghc-debian-armhf_llvm_abi.patch new file mode 100644 index 0000000..c3b045e --- /dev/null +++ b/ghc-debian-armhf_llvm_abi.patch @@ -0,0 +1,26 @@ +Description: If we are on armhf, tell llvm to generate code for this ABI. Not + forwarded upstream, because they will do a more 'proper' patch. See upstream + bug #5914. +Author: Iain Lane + +Index: ghc/compiler/main/DriverPipeline.hs +=================================================================== +--- ghc.orig/compiler/main/DriverPipeline.hs 2012-03-10 16:41:46.000000000 +0000 ++++ ghc/compiler/main/DriverPipeline.hs 2012-03-10 16:42:59.209169474 +0000 +@@ -1,5 +1,5 @@ + {-# OPTIONS -fno-cse #-} +-{-# LANGUAGE NamedFieldPuns #-} ++{-# LANGUAGE NamedFieldPuns, CPP #-} + -- -fno-cse is needed for GLOBAL_VAR's to behave properly + + ----------------------------------------------------------------------------- +@@ -1379,6 +1379,9 @@ + then ["-mattr=+v7,+vfp3"] + else if (elem VFPv3D16 ext) + then ["-mattr=+v7,+vfp3,+d16"] ++#ifdef __ARM_PCS_VFP ++ ++ ["-float-abi=hard"] ++#endif + else [] + _ -> [] + diff --git a/ghc.spec b/ghc.spec index fe02411..903321f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -98,8 +98,9 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch # Debian armel fixes Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch -# need to tell llc to use hard float on armv7hl -Patch12: ghc-7.4.1-armv7hl-llc-hard-float.patch +# Debian armhf fixes +Patch12: ghc-debian-ARM-VFPv3D16.patch +Patch13: ghc-debian-armhf_llvm_abi.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -218,7 +219,12 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %ifarch armv7hl armv5tel %patch10 -p1 -b .arm1 %patch11 -p1 -b .arm2 +%endif +%ifarch armv7hl +# touches aclocal.m4 %patch12 -p1 -b .arm +%patch13 -p1 -b .arm +autoreconf %endif %build @@ -235,6 +241,9 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif +%ifarch armv7hl +SRC_HC_OPTS += -D__ARM_PCS_VFP +%endif EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -421,8 +430,7 @@ fi * Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 - build with llvm-3.0 on ARM - remove arm from unregisterised_archs -- add Debian ARM register patches (Iain Lane) -- make llc use -float-abi=hard on armv7hl (thanks Debian and Ubuntu) +- add 4 Debian ARM patches for armel and armhf (Iain Lane) - bootstrap build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 From 44efb6d4e3f6b564fe3d98edb3352e33ab071b63 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Apr 2012 23:48:28 +0900 Subject: [PATCH 324/530] BR autoconf for armv7hl patch --- ghc.spec | 3 +++ 1 file changed, 3 insertions(+) diff --git a/ghc.spec b/ghc.spec index 903321f..e0a9c3d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -77,6 +77,9 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif +%ifarch armv7hl +BuildRequires: autoconf +%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} From c191f549423352866b9cbeb8166f848548473ffb Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 28 Apr 2012 13:37:49 +0900 Subject: [PATCH 325/530] full build for ARM --- ghc.spec | 18 ++++++++++-------- 1 file changed, 10 insertions(+), 8 deletions(-) diff --git a/ghc.spec b/ghc.spec index e0a9c3d..061bd22 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_hscolour 1 -%global without_testsuite 1 +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_hscolour 1 +#%%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 1.1%{?dist} +Release: 3%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -430,11 +430,13 @@ fi %files libraries %changelog -* Tue Apr 10 2012 Jens Petersen - 7.4.1-1.1 +* Sat Apr 28 2012 Jens Petersen - 7.4.1-3 - build with llvm-3.0 on ARM -- remove arm from unregisterised_archs +- remove ARM from unregisterised_archs - add 4 Debian ARM patches for armel and armhf (Iain Lane) -- bootstrap build + +* Wed Mar 21 2012 Jens Petersen - 7.4.1-2 +- full build * Wed Feb 15 2012 Jens Petersen - 7.4.1-1 - update to new 7.4.1 major release From 14ae8832d2ae5b1327a2eaf779a2885e9d7dcb76 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 May 2012 19:54:30 +0900 Subject: [PATCH 326/530] ghc-wrapper-libffi-include.patch for "missing libffi.h" when compiling prof on secondary archs eg on armv7: [ 1 of 21] Compiling Data.Functor.Product ( Data/Functor/Product.hs, dist/build/Data/Functor/Product.p_o ) /tmp/ghc1692_0/ghc1692_0.c:4:17: fatal error: ffi.h: No such file or directory --- ghc-wrapper-libffi-include.patch | 6 ++++++ ghc.spec | 26 ++++++++++++++++++-------- 2 files changed, 24 insertions(+), 8 deletions(-) create mode 100644 ghc-wrapper-libffi-include.patch diff --git a/ghc-wrapper-libffi-include.patch b/ghc-wrapper-libffi-include.patch new file mode 100644 index 0000000..48870ec --- /dev/null +++ b/ghc-wrapper-libffi-include.patch @@ -0,0 +1,6 @@ +diff -u ghc-7.4.1/ghc/ghc.wrapper\~ ghc-7.4.1/ghc/ghc.wrapper +--- ghc-7.4.1/ghc/ghc.wrapper~ 2012-02-02 03:10:32.000000000 +0900 ++++ ghc-7.4.1/ghc/ghc.wrapper 2012-05-02 19:39:05.503872527 +0900 +@@ -1 +1 @@ +-exec "$executablename" -B"$topdir" ${1+"$@"} ++exec "$executablename" -B"$topdir" -optc-I$(pkg-config --variable=includedir libffi) ${1+"$@"} diff --git a/ghc.spec b/ghc.spec index 061bd22..eacba93 100644 --- a/ghc.spec +++ b/ghc.spec @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 3%{?dist} +Release: 4%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -98,12 +98,14 @@ Patch7: ghc-powerpc-pthread.patch Patch8: ghc-powerpc-linker-mmap.patch # fix dynamic linking of executables using Template Haskell Patch9: Cabal-fix-dynamic-exec-for-TH.patch +# add libffi include dir to ghc wrapper for archs using gcc/llc +Patch10: ghc-wrapper-libffi-include.patch # Debian armel fixes -Patch10: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch -Patch11: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch +Patch11: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch +Patch12: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch # Debian armhf fixes -Patch12: ghc-debian-ARM-VFPv3D16.patch -Patch13: ghc-debian-armhf_llvm_abi.patch +Patch13: ghc-debian-ARM-VFPv3D16.patch +Patch14: ghc-debian-armhf_llvm_abi.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -218,15 +220,19 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch9 -p1 -b .orig +%ifnarch %{ix86} x86_64 +%patch10 -p1 -b .10-ffi +%endif + # ARM patches %ifarch armv7hl armv5tel -%patch10 -p1 -b .arm1 -%patch11 -p1 -b .arm2 +%patch11 -p1 -b .arm1 +%patch12 -p1 -b .arm2 %endif %ifarch armv7hl # touches aclocal.m4 -%patch12 -p1 -b .arm %patch13 -p1 -b .arm +%patch14 -p1 -b .arm autoreconf %endif @@ -430,6 +436,10 @@ fi %files libraries %changelog +* Wed May 2 2012 Jens Petersen - 7.4.1-4 +- add ghc-wrapper-libffi-include.patch to workaround "missing libffi.h" + for prof compiling on secondary archs + * Sat Apr 28 2012 Jens Petersen - 7.4.1-3 - build with llvm-3.0 on ARM - remove ARM from unregisterised_archs From 4193d0ec1bdff4da38fd1fbc2b60d6ebb7d8960a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 7 May 2012 23:41:50 +0900 Subject: [PATCH 327/530] update-package.sh long moved to haskell-sig/rebuild/ --- update-package.sh | 16 ---------------- 1 file changed, 16 deletions(-) delete mode 100755 update-package.sh diff --git a/update-package.sh b/update-package.sh deleted file mode 100755 index ef60175..0000000 --- a/update-package.sh +++ /dev/null @@ -1,16 +0,0 @@ -#!/bin/sh - -[ $# -ne 1 ] && echo "Usage: $(basename $0) [package]" && exit 1 - -set -e -x - -PKG=$1 - -cd ~/fedora/haskell/$PKG/master -git pull - -cat ~/fedora/haskell/cabal2spec/master/cabal2spec-0.22.4.diff | sed -e "s/@PKG@/$PKG/" | patch -p1 - -rpmdev-bumpspec --comment="update to cabal2spec-0.22.4" $PKG.spec - -fedpkg commit -p -m "update to cabal2spec-0.22.4" From 2238c4b2a9ebb9167b476df5344225b1eaef36ef Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 15 Jun 2012 16:55:18 +0900 Subject: [PATCH 328/530] use ghc_lib_subpackage instead of ghc_binlib_package --- ghc.spec | 56 +++++++++++++++++++++++++++++--------------------------- 1 file changed, 29 insertions(+), 27 deletions(-) diff --git a/ghc.spec b/ghc.spec index eacba93..2bc42cd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -24,13 +24,13 @@ Name: ghc # part of haskell-platform -# NB make sure to rebuild ghc after a version bump to avoid ABI change problems +# ghc must be rebuilt after a version bump to avoid ABI change problems Version: 7.4.1 # Since library subpackages are versioned: # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 4%{?dist} +Release: 5%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -54,7 +54,7 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -BuildRequires: ghc-rpm-macros >= 0.14 +BuildRequires: ghc-rpm-macros >= 0.91 BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -91,8 +91,6 @@ Patch2: ghc-gen_contents_index-type-level.patch Patch3: ghc-gen_contents_index-cron-batch.patch # fedora does not allow copy libraries Patch4: ghc-use-system-libffi.patch -# add cabal configure option --enable-executable-dynamic -# (see http://hackage.haskell.org/trac/hackage/ticket/600) Patch7: ghc-powerpc-pthread.patch # http://hackage.haskell.org/trac/ghc/ticket/4999 Patch8: ghc-powerpc-linker-mmap.patch @@ -133,6 +131,7 @@ License: BSD Group: Development/Languages Requires: gcc%{?_isa} Requires: ghc-base-devel%{?_isa} +# for alternatives Requires(post): chkconfig Requires(postun): chkconfig # added in f14 @@ -158,31 +157,31 @@ To install all of ghc, install the ghc base package. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_binlib_package Cabal 1.14.0 -%ghc_binlib_package -l %BSDHaskellReport array 0.4.0.0 -%ghc_binlib_package -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.0.0 -%ghc_binlib_package binary 0.5.1.0 -%ghc_binlib_package bytestring 0.9.2.1 -%ghc_binlib_package -l %BSDHaskellReport containers 0.4.2.1 -%ghc_binlib_package -l %BSDHaskellReport deepseq 1.3.0.0 -%ghc_binlib_package -l %BSDHaskellReport directory 1.1.0.2 -%ghc_binlib_package -l %BSDHaskellReport extensible-exceptions 0.1.1.4 -%ghc_binlib_package filepath 1.3.0.0 +%ghc_lib_subpackage Cabal 1.14.0 +%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.0.0 +%ghc_lib_subpackage binary 0.5.1.0 +%ghc_lib_subpackage bytestring 0.9.2.1 +%ghc_lib_subpackage -l %BSDHaskellReport containers 0.4.2.1 +%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport directory 1.1.0.2 +%ghc_lib_subpackage -l %BSDHaskellReport extensible-exceptions 0.1.1.4 +%ghc_lib_subpackage filepath 1.3.0.0 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: -%ghc_binlib_package -x ghc %{ghc_version_override} +%ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_binlib_package -l HaskellReport haskell2010 1.1.0.1 -%ghc_binlib_package -l HaskellReport haskell98 2.0.0.1 -%ghc_binlib_package hoopl 3.8.7.3 -%ghc_binlib_package hpc 0.5.1.1 -%ghc_binlib_package -l %BSDHaskellReport old-locale 1.0.0.4 -%ghc_binlib_package -l %BSDHaskellReport old-time 1.1.0.0 -%ghc_binlib_package pretty 1.1.1.0 -%ghc_binlib_package -l %BSDHaskellReport process 1.1.0.1 -%ghc_binlib_package template-haskell 2.7.0.0 -%ghc_binlib_package time 1.4 -%ghc_binlib_package unix 2.5.1.0 +%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.0.1 +%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.1 +%ghc_lib_subpackage hoopl 3.8.7.3 +%ghc_lib_subpackage hpc 0.5.1.1 +%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.4 +%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.0 +%ghc_lib_subpackage pretty 1.1.1.0 +%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.1 +%ghc_lib_subpackage template-haskell 2.7.0.0 +%ghc_lib_subpackage time 1.4 +%ghc_lib_subpackage unix 2.5.1.0 %endif %global version %{ghc_version_override} @@ -436,6 +435,9 @@ fi %files libraries %changelog +* Fri Jun 15 2012 Jens Petersen - 7.4.1-5 +- use ghc_lib_subpackage instead of ghc_binlib_package (ghc-rpm-macros 0.91) + * Wed May 2 2012 Jens Petersen - 7.4.1-4 - add ghc-wrapper-libffi-include.patch to workaround "missing libffi.h" for prof compiling on secondary archs From a27c47f9d9df23a495c89a432dece196649ea58f Mon Sep 17 00:00:00 2001 From: Dennis Gilmore Date: Thu, 19 Jul 2012 00:11:59 -0500 Subject: [PATCH 329/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 2bc42cd..6ae21bd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -30,7 +30,7 @@ Version: 7.4.1 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 5%{?dist} +Release: 6%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -435,6 +435,9 @@ fi %files libraries %changelog +* Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild + * Fri Jun 15 2012 Jens Petersen - 7.4.1-5 - use ghc_lib_subpackage instead of ghc_binlib_package (ghc-rpm-macros 0.91) From 6b98066a85d2a9e1666c6ac7ee5e8210d9eb887a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Aug 2012 16:30:44 +0900 Subject: [PATCH 330/530] update to 7.4.2 bootstrap - drop arm StgCRun patches - update arm hf patch - use _smp_mflags --- .gitignore | 2 + ...to-not-save-and-restore-r11-fp-regis.patch | 29 - ...n-clobbered-register-list-for-both-A.patch | 34 - ...rt-for-ARM-hard-float-ABI-fixes-5914.patch | 1274 +++++++++++++++++ ghc-debian-ARM-VFPv3D16.patch | 16 - ghc-debian-armhf_llvm_abi.patch | 26 - ghc.spec | 47 +- sources | 3 +- 8 files changed, 1297 insertions(+), 134 deletions(-) delete mode 100644 fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch delete mode 100644 fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch create mode 100644 ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch delete mode 100644 ghc-debian-ARM-VFPv3D16.patch delete mode 100644 ghc-debian-armhf_llvm_abi.patch diff --git a/.gitignore b/.gitignore index fb09fbc..6f437bb 100644 --- a/.gitignore +++ b/.gitignore @@ -7,3 +7,5 @@ testsuite-6.12.3.tar.bz2 /testsuite-7.0.4.tar.bz2 /ghc-7.4.1-testsuite.tar.bz2 /ghc-7.4.1-src.tar.bz2 +/ghc-7.4.2-src.tar.bz2 +/ghc-7.4.2-testsuite.tar.bz2 diff --git a/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch b/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch deleted file mode 100644 index 98772f1..0000000 --- a/fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch +++ /dev/null @@ -1,29 +0,0 @@ -From 1cbf3bcae87dd102942d85ce71ea17d42d4b5f5a Mon Sep 17 00:00:00 2001 -From: Karel Gardas -Date: Tue, 14 Feb 2012 08:03:07 +0100 -Subject: [PATCH 2/2] fix ARM StgCRun to not save and restore r11/fp register twice - ---- - rts/StgCRun.c | 4 ++-- - 1 files changed, 2 insertions(+), 2 deletions(-) - ---- a/rts/StgCRun.c -+++ b/rts/StgCRun.c -@@ -632,7 +632,7 @@ - /* - * save callee-saves registers on behalf of the STG code. - */ -- "stmfd sp!, {r4-r11, fp, ip, lr}\n\t" -+ "stmfd sp!, {r4-r10, fp, ip, lr}\n\t" - #if !defined(arm_HOST_ARCH_PRE_ARMv6) - "vstmdb sp!, {d8-d11}\n\t" - #endif -@@ -669,7 +669,7 @@ - #if !defined(arm_HOST_ARCH_PRE_ARMv6) - "vldmia sp!, {d8-d11}\n\t" - #endif -- "ldmfd sp!, {r4-r11, fp, ip, lr}\n\t" -+ "ldmfd sp!, {r4-r10, fp, ip, lr}\n\t" - : "=r" (r) - : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) - #if !defined(__thumb__) diff --git a/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch b/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch deleted file mode 100644 index f033c18..0000000 --- a/fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch +++ /dev/null @@ -1,34 +0,0 @@ -From 957f778cb971d63cbbea0c71c727c94474b1b905 Mon Sep 17 00:00:00 2001 -From: Karel Gardas -Date: Tue, 14 Feb 2012 08:01:47 +0100 -Subject: [PATCH 1/2] fix ARM's StgCRun clobbered register list for both ARM and Thumb modes - ---- - rts/StgCRun.c | 16 +++++++++++++++- - 1 files changed, 15 insertions(+), 1 deletions(-) - ---- a/rts/StgCRun.c -+++ b/rts/StgCRun.c -@@ -672,7 +672,21 @@ - "ldmfd sp!, {r4-r11, fp, ip, lr}\n\t" - : "=r" (r) - : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) -- : "%r4", "%r5", "%r6", "%r8", "%r9", "%r10", "%r11", "%fp", "%ip", "%lr" -+#if !defined(__thumb__) -+ /* In ARM mode, r11/fp is frame-pointer and so we cannot mark -+ it as clobbered. If we do so, GCC complains with error. */ -+ : "%r4", "%r5", "%r6", "%r7", "%r8", "%r9", "%r10", "%ip", "%lr" -+#else -+ /* In Thumb mode r7 is frame-pointer and so we cannot mark it -+ as clobbered. On the other hand we mark as clobbered also -+ those regs not used in Thumb mode. Hard to judge if this is -+ needed, but certainly Haskell code is using them for -+ placing GHC's virtual registers there. See -+ includes/stg/MachRegs.h Please note that Haskell code is -+ compiled by GHC/LLVM into ARM code (not Thumb!), at least -+ as of February 2012 */ -+ : "%r4", "%r5", "%r6", "%r8", "%r9", "%r10", "%fp", "%ip", "%lr" -+#endif - ); - return r; - } diff --git a/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch b/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch new file mode 100644 index 0000000..a9b897b --- /dev/null +++ b/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch @@ -0,0 +1,1274 @@ +From 83195ff5ba73779514e3d06b1457d45f849c7fc2 Mon Sep 17 00:00:00 2001 +From: Karel Gardas +Date: Wed, 25 Apr 2012 09:04:50 +0200 +Subject: [PATCH] add support for ARM hard-float ABI (fixes #5914) + +This patch enhances Platform's ArchARM to include ARM ABI value. It also +tweaks configure machinery to detect hard-float ABI and to set it wherever +needed. Finally when hard-float ABI is in use, pass appropriate compiler +option to the LLVM's llc. Fixes #5914. +--- + aclocal.m4 | 2 +- + compiler/main/DriverPipeline.hs | 16 +- + compiler/nativeGen/AsmCodeGen.lhs | 2 +- + compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 56 ++-- + compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs | 14 +- + compiler/nativeGen/RegAlloc/Linear/Main.hs | 14 +- + compiler/nativeGen/TargetReg.hs | 70 ++-- + compiler/utils/Platform.hs | 12 +- + config.guess | 482 ++++++++++---------- + configure.ac | 14 + + 10 files changed, 345 insertions(+), 337 deletions(-) + +diff --git a/aclocal.m4 b/aclocal.m4 +index 5652185..c196bdf 100644 +--- a/aclocal.m4 ++++ b/aclocal.m4 +@@ -171,7 +171,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], + ;; + arm) + GET_ARM_ISA() +- test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT}\"" ++ test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" + ;; + alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + test -z "[$]2" || eval "[$]2=ArchUnknown" +diff -u ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs +--- ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm 2012-05-15 02:10:41.000000000 +0900 ++++ ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs 2012-05-18 12:19:22.779955285 +0900 +@@ -1366,7 +1366,8 @@ + SysTools.FileOption "" input_fn, + SysTools.Option "-o", SysTools.FileOption "" output_fn] + ++ map SysTools.Option lc_opts +- ++ map SysTools.Option fpOpts) ++ ++ map SysTools.Option fpOpts ++ ++ map SysTools.Option abiOpts) + + return (next_phase, output_fn) + where +@@ -1378,12 +1379,19 @@ + -- while compiling GHC source code. It's probably due to fact that it + -- does not enable VFP by default. Let's do this manually here + fpOpts = case platformArch (targetPlatform dflags) of +- ArchARM ARMv7 ext -> if (elem VFPv3 ext) ++ ArchARM ARMv7 ext _ -> if (elem VFPv3 ext) + then ["-mattr=+v7,+vfp3"] + else if (elem VFPv3D16 ext) + then ["-mattr=+v7,+vfp3,+d16"] + else [] + _ -> [] ++ -- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still ++ -- compiles into soft-float ABI. We need to explicitly set abi ++ -- to hard ++ abiOpts = case platformArch (targetPlatform dflags) of ++ ArchARM ARMv7 _ HARD -> ["-float-abi=hard"] ++ ArchARM ARMv7 _ _ -> [] ++ _ -> [] + + ----------------------------------------------------------------------------- + -- LlvmMangle phase +@@ -1532,8 +1540,8 @@ + + elfSectionNote :: String + elfSectionNote = case platformArch (targetPlatform dflags) of +- ArchARM _ _ -> "%note" +- _ -> "@note" ++ ArchARM _ _ _ -> "%note" ++ _ -> "@note" + + -- The "link info" is a string representing the parameters of the + -- link. We save this information in the binary, and the next time we +diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs +index 1ad1242..e976e58 100644 +--- a/compiler/nativeGen/AsmCodeGen.lhs ++++ b/compiler/nativeGen/AsmCodeGen.lhs +@@ -200,7 +200,7 @@ nativeCodeGen dflags h us cmms + ,ncgExpandTop = map SPARC.CodeGen.Expand.expandTop + ,ncgMakeFarBranches = id + } +- ArchARM _ _ -> ++ ArchARM _ _ _ -> + panic "nativeCodeGen: No NCG for ARM" + ArchPPC_64 -> + panic "nativeCodeGen: No NCG for PPC 64" +diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +index 6067f23..6cd3f00 100644 +--- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs ++++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +@@ -107,13 +107,13 @@ trivColorable + trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts exclusions + | let !cALLOCATABLE_REGS_INTEGER + = iUnbox (case platformArch platform of +- ArchX86 -> 3 +- ArchX86_64 -> 5 +- ArchPPC -> 16 +- ArchSPARC -> 14 +- ArchPPC_64 -> panic "trivColorable ArchPPC_64" +- ArchARM _ _ -> panic "trivColorable ArchARM" +- ArchUnknown -> panic "trivColorable ArchUnknown") ++ ArchX86 -> 3 ++ ArchX86_64 -> 5 ++ ArchPPC -> 16 ++ ArchSPARC -> 14 ++ ArchPPC_64 -> panic "trivColorable ArchPPC_64" ++ ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchUnknown -> panic "trivColorable ArchUnknown") + , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_INTEGER + (virtualRegSqueeze RcInteger) + conflicts +@@ -127,13 +127,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl + trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions + | let !cALLOCATABLE_REGS_FLOAT + = iUnbox (case platformArch platform of +- ArchX86 -> 0 +- ArchX86_64 -> 0 +- ArchPPC -> 0 +- ArchSPARC -> 22 +- ArchPPC_64 -> panic "trivColorable ArchPPC_64" +- ArchARM _ _ -> panic "trivColorable ArchARM" +- ArchUnknown -> panic "trivColorable ArchUnknown") ++ ArchX86 -> 0 ++ ArchX86_64 -> 0 ++ ArchPPC -> 0 ++ ArchSPARC -> 22 ++ ArchPPC_64 -> panic "trivColorable ArchPPC_64" ++ ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchUnknown -> panic "trivColorable ArchUnknown") + , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_FLOAT + (virtualRegSqueeze RcFloat) + conflicts +@@ -147,13 +147,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus + trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions + | let !cALLOCATABLE_REGS_DOUBLE + = iUnbox (case platformArch platform of +- ArchX86 -> 6 +- ArchX86_64 -> 0 +- ArchPPC -> 26 +- ArchSPARC -> 11 +- ArchPPC_64 -> panic "trivColorable ArchPPC_64" +- ArchARM _ _ -> panic "trivColorable ArchARM" +- ArchUnknown -> panic "trivColorable ArchUnknown") ++ ArchX86 -> 6 ++ ArchX86_64 -> 0 ++ ArchPPC -> 26 ++ ArchSPARC -> 11 ++ ArchPPC_64 -> panic "trivColorable ArchPPC_64" ++ ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchUnknown -> panic "trivColorable ArchUnknown") + , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_DOUBLE + (virtualRegSqueeze RcDouble) + conflicts +@@ -167,13 +167,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu + trivColorable platform virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts exclusions + | let !cALLOCATABLE_REGS_SSE + = iUnbox (case platformArch platform of +- ArchX86 -> 8 +- ArchX86_64 -> 10 +- ArchPPC -> 0 +- ArchSPARC -> 0 +- ArchPPC_64 -> panic "trivColorable ArchPPC_64" +- ArchARM _ _ -> panic "trivColorable ArchARM" +- ArchUnknown -> panic "trivColorable ArchUnknown") ++ ArchX86 -> 8 ++ ArchX86_64 -> 10 ++ ArchPPC -> 0 ++ ArchSPARC -> 0 ++ ArchPPC_64 -> panic "trivColorable ArchPPC_64" ++ ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchUnknown -> panic "trivColorable ArchUnknown") + , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_SSE + (virtualRegSqueeze RcDoubleSSE) + conflicts +diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +index 6fbbd04..fd1fd27 100644 +--- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs ++++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +@@ -68,11 +68,11 @@ instance FR SPARC.FreeRegs where + maxSpillSlots :: Platform -> Int + maxSpillSlots platform + = case platformArch platform of +- ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit +- ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit +- ArchPPC -> PPC.Instr.maxSpillSlots +- ArchSPARC -> SPARC.Instr.maxSpillSlots +- ArchARM _ _ -> panic "maxSpillSlots ArchARM" +- ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" +- ArchUnknown -> panic "maxSpillSlots ArchUnknown" ++ ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit ++ ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit ++ ArchPPC -> PPC.Instr.maxSpillSlots ++ ArchSPARC -> SPARC.Instr.maxSpillSlots ++ ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" ++ ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" ++ ArchUnknown -> panic "maxSpillSlots ArchUnknown" + +diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs +index fc0bde4..64b0f68 100644 +--- a/compiler/nativeGen/RegAlloc/Linear/Main.hs ++++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs +@@ -180,13 +180,13 @@ linearRegAlloc + linearRegAlloc dflags first_id block_live sccs + = let platform = targetPlatform dflags + in case platformArch platform of +- ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs +- ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs +- ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs +- ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs +- ArchARM _ _ -> panic "linearRegAlloc ArchARM" +- ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" +- ArchUnknown -> panic "linearRegAlloc ArchUnknown" ++ ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs ++ ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs ++ ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs ++ ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs ++ ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" ++ ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" ++ ArchUnknown -> panic "linearRegAlloc ArchUnknown" + + linearRegAlloc' + :: (FR freeRegs, PlatformOutputable instr, Instruction instr) +diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs +index cbc4c17..13293de 100644 +--- a/compiler/nativeGen/TargetReg.hs ++++ b/compiler/nativeGen/TargetReg.hs +@@ -50,35 +50,35 @@ import qualified SPARC.Regs as SPARC + targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt + targetVirtualRegSqueeze platform + = case platformArch platform of +- ArchX86 -> X86.virtualRegSqueeze +- ArchX86_64 -> X86.virtualRegSqueeze +- ArchPPC -> PPC.virtualRegSqueeze +- ArchSPARC -> SPARC.virtualRegSqueeze +- ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" +- ArchARM _ _ -> panic "targetVirtualRegSqueeze ArchARM" +- ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" ++ ArchX86 -> X86.virtualRegSqueeze ++ ArchX86_64 -> X86.virtualRegSqueeze ++ ArchPPC -> PPC.virtualRegSqueeze ++ ArchSPARC -> SPARC.virtualRegSqueeze ++ ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" ++ ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" ++ ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" + + targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt + targetRealRegSqueeze platform + = case platformArch platform of +- ArchX86 -> X86.realRegSqueeze +- ArchX86_64 -> X86.realRegSqueeze +- ArchPPC -> PPC.realRegSqueeze +- ArchSPARC -> SPARC.realRegSqueeze +- ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" +- ArchARM _ _ -> panic "targetRealRegSqueeze ArchARM" +- ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" ++ ArchX86 -> X86.realRegSqueeze ++ ArchX86_64 -> X86.realRegSqueeze ++ ArchPPC -> PPC.realRegSqueeze ++ ArchSPARC -> SPARC.realRegSqueeze ++ ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" ++ ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" ++ ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" + + targetClassOfRealReg :: Platform -> RealReg -> RegClass + targetClassOfRealReg platform + = case platformArch platform of +- ArchX86 -> X86.classOfRealReg +- ArchX86_64 -> X86.classOfRealReg +- ArchPPC -> PPC.classOfRealReg +- ArchSPARC -> SPARC.classOfRealReg +- ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" +- ArchARM _ _ -> panic "targetClassOfRealReg ArchARM" +- ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" ++ ArchX86 -> X86.classOfRealReg ++ ArchX86_64 -> X86.classOfRealReg ++ ArchPPC -> PPC.classOfRealReg ++ ArchSPARC -> SPARC.classOfRealReg ++ ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" ++ ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" ++ ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" + + -- TODO: This should look at targetPlatform too + targetWordSize :: Size +@@ -87,24 +87,24 @@ targetWordSize = intSize wordWidth + targetMkVirtualReg :: Platform -> Unique -> Size -> VirtualReg + targetMkVirtualReg platform + = case platformArch platform of +- ArchX86 -> X86.mkVirtualReg +- ArchX86_64 -> X86.mkVirtualReg +- ArchPPC -> PPC.mkVirtualReg +- ArchSPARC -> SPARC.mkVirtualReg +- ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" +- ArchARM _ _ -> panic "targetMkVirtualReg ArchARM" +- ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" ++ ArchX86 -> X86.mkVirtualReg ++ ArchX86_64 -> X86.mkVirtualReg ++ ArchPPC -> PPC.mkVirtualReg ++ ArchSPARC -> SPARC.mkVirtualReg ++ ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" ++ ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" ++ ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" + + targetRegDotColor :: Platform -> RealReg -> SDoc + targetRegDotColor platform + = case platformArch platform of +- ArchX86 -> X86.regDotColor platform +- ArchX86_64 -> X86.regDotColor platform +- ArchPPC -> PPC.regDotColor +- ArchSPARC -> SPARC.regDotColor +- ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" +- ArchARM _ _ -> panic "targetRegDotColor ArchARM" +- ArchUnknown -> panic "targetRegDotColor ArchUnknown" ++ ArchX86 -> X86.regDotColor platform ++ ArchX86_64 -> X86.regDotColor platform ++ ArchPPC -> PPC.regDotColor ++ ArchSPARC -> SPARC.regDotColor ++ ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" ++ ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" ++ ArchUnknown -> panic "targetRegDotColor ArchUnknown" + + + targetClassOfReg :: Platform -> Reg -> RegClass +diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs +index 47dd779..8252621 100644 +--- a/compiler/utils/Platform.hs ++++ b/compiler/utils/Platform.hs +@@ -7,6 +7,7 @@ module Platform ( + OS(..), + ArmISA(..), + ArmISAExt(..), ++ ArmABI(..), + + target32Bit, + osElfTarget +@@ -41,7 +42,9 @@ data Arch + | ArchSPARC + | ArchARM + { armISA :: ArmISA +- , armISAExt :: [ArmISAExt] } ++ , armISAExt :: [ArmISAExt] ++ , armABI :: ArmABI ++ } + deriving (Read, Show, Eq) + + +@@ -61,7 +64,7 @@ data OS + | OSHaiku + deriving (Read, Show, Eq) + +--- | ARM Instruction Set Architecture and Extensions ++-- | ARM Instruction Set Architecture, Extensions and ABI + -- + data ArmISA + = ARMv5 +@@ -77,6 +80,11 @@ data ArmISAExt + | IWMMX2 + deriving (Read, Show, Eq) + ++data ArmABI ++ = SOFT ++ | SOFTFP ++ | HARD ++ deriving (Read, Show, Eq) + + target32Bit :: Platform -> Bool + target32Bit p = platformWordSize p == 4 +diff --git a/config.guess b/config.guess +index 463a03a..d622a44 100644 +--- a/config.guess ++++ b/config.guess +@@ -1,10 +1,10 @@ + #! /bin/sh + # Attempt to guess a canonical system name. + # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, +-# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008 +-# Free Software Foundation, Inc. ++# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, ++# 2011, 2012 Free Software Foundation, Inc. + +-timestamp='2008-11-15' ++timestamp='2012-02-10' + + # This file is free software; you can redistribute it and/or modify it + # under the terms of the GNU General Public License as published by +@@ -17,9 +17,7 @@ timestamp='2008-11-15' + # General Public License for more details. + # + # You should have received a copy of the GNU General Public License +-# along with this program; if not, write to the Free Software +-# Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA +-# 02110-1301, USA. ++# along with this program; if not, see . + # + # As a special exception to the GNU General Public License, if you + # distribute this file as part of a program that contains a +@@ -27,16 +25,16 @@ timestamp='2008-11-15' + # the same distribution terms that you use for the rest of that program. + + +-# Originally written by Per Bothner . +-# Please send patches to . Submit a context +-# diff and a properly formatted ChangeLog entry. ++# Originally written by Per Bothner. Please send patches (context ++# diff format) to and include a ChangeLog ++# entry. + # + # This script attempts to guess a canonical system name similar to + # config.sub. If it succeeds, it prints the system name on stdout, and + # exits with 0. Otherwise, it exits with 1. + # +-# The plan is that this can be called by configure scripts if you +-# don't specify an explicit build system type. ++# You can get the latest version of this script from: ++# http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess;hb=HEAD + + me=`echo "$0" | sed -e 's,.*/,,'` + +@@ -56,8 +54,9 @@ version="\ + GNU config.guess ($timestamp) + + Originally written by Per Bothner. +-Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, +-2002, 2003, 2004, 2005, 2006, 2007, 2008 Free Software Foundation, Inc. ++Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, ++2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012 ++Free Software Foundation, Inc. + + This is free software; see the source for copying conditions. There is NO + warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." +@@ -144,7 +143,7 @@ UNAME_VERSION=`(uname -v) 2>/dev/null` || UNAME_VERSION=unknown + case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + *:NetBSD:*:*) + # NetBSD (nbsd) targets should (where applicable) match one or +- # more of the tupples: *-*-netbsdelf*, *-*-netbsdaout*, ++ # more of the tuples: *-*-netbsdelf*, *-*-netbsdaout*, + # *-*-netbsdecoff* and *-*-netbsd*. For targets that recently + # switched to ELF, *-*-netbsd* would select the old + # object file format. This provides both forward +@@ -170,7 +169,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + arm*|i386|m68k|ns32k|sh3*|sparc|vax) + eval $set_cc_for_build + if echo __ELF__ | $CC_FOR_BUILD -E - 2>/dev/null \ +- | grep __ELF__ >/dev/null ++ | grep -q __ELF__ + then + # Once all utilities can be ECOFF (netbsdecoff) or a.out (netbsdaout). + # Return netbsd for either. FIX? +@@ -180,7 +179,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + fi + ;; + *) +- os=netbsd ++ os=netbsd + ;; + esac + # The OS release +@@ -223,7 +222,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $3}'` + ;; + *5.*) +- UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` ++ UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` + ;; + esac + # According to Compaq, /usr/sbin/psrinfo has been available on +@@ -269,7 +268,10 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + # A Xn.n version is an unreleased experimental baselevel. + # 1.2 uses "1.2" for uname -r. + echo ${UNAME_MACHINE}-dec-osf`echo ${UNAME_RELEASE} | sed -e 's/^[PVTX]//' | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` +- exit ;; ++ # Reset EXIT trap before exiting to avoid spurious non-zero exit code. ++ exitcode=$? ++ trap '' 0 ++ exit $exitcode ;; + Alpha\ *:Windows_NT*:*) + # How do we know it's Interix rather than the generic POSIX subsystem? + # Should we change UNAME_MACHINE based on the output of uname instead +@@ -295,7 +297,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + echo s390-ibm-zvmoe + exit ;; + *:OS400:*:*) +- echo powerpc-ibm-os400 ++ echo powerpc-ibm-os400 + exit ;; + arm:RISC*:1.[012]*:*|arm:riscix:1.[012]*:*) + echo arm-acorn-riscix${UNAME_RELEASE} +@@ -324,12 +326,18 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + case `/usr/bin/uname -p` in + sparc) echo sparc-icl-nx7; exit ;; + esac ;; ++ s390x:SunOS:*:*) ++ echo ${UNAME_MACHINE}-ibm-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` ++ exit ;; + sun4H:SunOS:5.*:*) + echo sparc-hal-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` + exit ;; + sun4*:SunOS:5.*:* | tadpole*:SunOS:5.*:*) + echo sparc-sun-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` + exit ;; ++ i86pc:AuroraUX:5.*:* | i86xen:AuroraUX:5.*:*) ++ echo i386-pc-auroraux${UNAME_RELEASE} ++ exit ;; + i86pc:SunOS:5.*:* | i86xen:SunOS:5.*:*) + eval $set_cc_for_build + SUN_ARCH="i386" +@@ -337,17 +345,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + # Note that the Sun cc does not turn __LP64__ into 1 like gcc does. + # This test works for both compilers. + if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then +- # bash is not able to generate correct code here +- # i.e. it leaves \ns there +- # so we need to use /usr/bin/echo to get what we want +- # note that if config.guess is run by /bin/sh then +- # this works as expected even without /usr/bin/echo +- # but the problem is that configure is clever enough +- # to find bash installed and then runs config.guess +- # by bash instead of by /bin/sh +- # It seems that using /usr/bin/echo here is the most +- # portable Solaris fix +- if /usr/bin/echo '\n#ifdef __amd64\nIS_64BIT_ARCH\n#endif' | \ ++ if (echo '#ifdef __amd64'; echo IS_64BIT_ARCH; echo '#endif') | \ + (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ + grep IS_64BIT_ARCH >/dev/null + then +@@ -398,23 +396,23 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in + # MiNT. But MiNT is downward compatible to TOS, so this should + # be no problem. + atarist[e]:*MiNT:*:* | atarist[e]:*mint:*:* | atarist[e]:*TOS:*:*) +- echo m68k-atari-mint${UNAME_RELEASE} ++ echo m68k-atari-mint${UNAME_RELEASE} + exit ;; + atari*:*MiNT:*:* | atari*:*mint:*:* | atarist[e]:*TOS:*:*) + echo m68k-atari-mint${UNAME_RELEASE} +- exit ;; ++ exit ;; + *falcon*:*MiNT:*:* | *falcon*:*mint:*:* | *falcon*:*TOS:*:*) +- echo m68k-atari-mint${UNAME_RELEASE} ++ echo m68k-atari-mint${UNAME_RELEASE} + exit ;; + milan*:*MiNT:*:* | milan*:*mint:*:* | *milan*:*TOS:*:*) +- echo m68k-milan-mint${UNAME_RELEASE} +- exit ;; ++ echo m68k-milan-mint${UNAME_RELEASE} ++ exit ;; + hades*:*MiNT:*:* | hades*:*mint:*:* | *hades*:*TOS:*:*) +- echo m68k-hades-mint${UNAME_RELEASE} +- exit ;; ++ echo m68k-hades-mint${UNAME_RELEASE} ++ exit ;; + *:*MiNT:*:* | *:*mint:*:* | *:*TOS:*:*) +- echo m68k-unknown-mint${UNAME_RELEASE} +- exit ;; ++ echo m68k-unknown-mint${UNAME_RELEASE} ++ exit ;; + m68k:machten:*:*) + echo m68k-apple-machten${UNAME_RELEASE} + exit ;; +@@ -484,8 +482,8 @@ EOF + echo m88k-motorola-sysv3 + exit ;; + AViiON:dgux:*:*) +- # DG/UX returns AViiON for all architectures +- UNAME_PROCESSOR=`/usr/bin/uname -p` ++ # DG/UX returns AViiON for all architectures ++ UNAME_PROCESSOR=`/usr/bin/uname -p` + if [ $UNAME_PROCESSOR = mc88100 ] || [ $UNAME_PROCESSOR = mc88110 ] + then + if [ ${TARGET_BINARY_INTERFACE}x = m88kdguxelfx ] || \ +@@ -498,7 +496,7 @@ EOF + else + echo i586-dg-dgux${UNAME_RELEASE} + fi +- exit ;; ++ exit ;; + M88*:DolphinOS:*:*) # DolphinOS (SVR3) + echo m88k-dolphin-sysv3 + exit ;; +@@ -555,7 +553,7 @@ EOF + echo rs6000-ibm-aix3.2 + fi + exit ;; +- *:AIX:*:[456]) ++ *:AIX:*:[4567]) + IBM_CPU_ID=`/usr/sbin/lsdev -C -c processor -S available | sed 1q | awk '{ print $1 }'` + if /usr/sbin/lsattr -El ${IBM_CPU_ID} | grep ' POWER' >/dev/null 2>&1; then + IBM_ARCH=rs6000 +@@ -598,52 +596,52 @@ EOF + 9000/[678][0-9][0-9]) + if [ -x /usr/bin/getconf ]; then + sc_cpu_version=`/usr/bin/getconf SC_CPU_VERSION 2>/dev/null` +- sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` +- case "${sc_cpu_version}" in +- 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 +- 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 +- 532) # CPU_PA_RISC2_0 +- case "${sc_kernel_bits}" in +- 32) HP_ARCH="hppa2.0n" ;; +- 64) HP_ARCH="hppa2.0w" ;; ++ sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` ++ case "${sc_cpu_version}" in ++ 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 ++ 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 ++ 532) # CPU_PA_RISC2_0 ++ case "${sc_kernel_bits}" in ++ 32) HP_ARCH="hppa2.0n" ;; ++ 64) HP_ARCH="hppa2.0w" ;; + '') HP_ARCH="hppa2.0" ;; # HP-UX 10.20 +- esac ;; +- esac ++ esac ;; ++ esac + fi + if [ "${HP_ARCH}" = "" ]; then + eval $set_cc_for_build +- sed 's/^ //' << EOF >$dummy.c ++ sed 's/^ //' << EOF >$dummy.c + +- #define _HPUX_SOURCE +- #include +- #include ++ #define _HPUX_SOURCE ++ #include ++ #include + +- int main () +- { +- #if defined(_SC_KERNEL_BITS) +- long bits = sysconf(_SC_KERNEL_BITS); +- #endif +- long cpu = sysconf (_SC_CPU_VERSION); ++ int main () ++ { ++ #if defined(_SC_KERNEL_BITS) ++ long bits = sysconf(_SC_KERNEL_BITS); ++ #endif ++ long cpu = sysconf (_SC_CPU_VERSION); + +- switch (cpu) +- { +- case CPU_PA_RISC1_0: puts ("hppa1.0"); break; +- case CPU_PA_RISC1_1: puts ("hppa1.1"); break; +- case CPU_PA_RISC2_0: +- #if defined(_SC_KERNEL_BITS) +- switch (bits) +- { +- case 64: puts ("hppa2.0w"); break; +- case 32: puts ("hppa2.0n"); break; +- default: puts ("hppa2.0"); break; +- } break; +- #else /* !defined(_SC_KERNEL_BITS) */ +- puts ("hppa2.0"); break; +- #endif +- default: puts ("hppa1.0"); break; +- } +- exit (0); +- } ++ switch (cpu) ++ { ++ case CPU_PA_RISC1_0: puts ("hppa1.0"); break; ++ case CPU_PA_RISC1_1: puts ("hppa1.1"); break; ++ case CPU_PA_RISC2_0: ++ #if defined(_SC_KERNEL_BITS) ++ switch (bits) ++ { ++ case 64: puts ("hppa2.0w"); break; ++ case 32: puts ("hppa2.0n"); break; ++ default: puts ("hppa2.0"); break; ++ } break; ++ #else /* !defined(_SC_KERNEL_BITS) */ ++ puts ("hppa2.0"); break; ++ #endif ++ default: puts ("hppa1.0"); break; ++ } ++ exit (0); ++ } + EOF + (CCOPTS= $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null) && HP_ARCH=`$dummy` + test -z "$HP_ARCH" && HP_ARCH=hppa +@@ -663,7 +661,7 @@ EOF + # => hppa64-hp-hpux11.23 + + if echo __LP64__ | (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | +- grep __LP64__ >/dev/null ++ grep -q __LP64__ + then + HP_ARCH="hppa2.0w" + else +@@ -734,22 +732,22 @@ EOF + exit ;; + C1*:ConvexOS:*:* | convex:ConvexOS:C1*:*) + echo c1-convex-bsd +- exit ;; ++ exit ;; + C2*:ConvexOS:*:* | convex:ConvexOS:C2*:*) + if getsysinfo -f scalar_acc + then echo c32-convex-bsd + else echo c2-convex-bsd + fi +- exit ;; ++ exit ;; + C34*:ConvexOS:*:* | convex:ConvexOS:C34*:*) + echo c34-convex-bsd +- exit ;; ++ exit ;; + C38*:ConvexOS:*:* | convex:ConvexOS:C38*:*) + echo c38-convex-bsd +- exit ;; ++ exit ;; + C4*:ConvexOS:*:* | convex:ConvexOS:C4*:*) + echo c4-convex-bsd +- exit ;; ++ exit ;; + CRAY*Y-MP:*:*:*) + echo ymp-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' + exit ;; +@@ -773,14 +771,14 @@ EOF + exit ;; + F30[01]:UNIX_System_V:*:* | F700:UNIX_System_V:*:*) + FUJITSU_PROC=`uname -m | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` +- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` +- FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` +- echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" +- exit ;; ++ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` ++ FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` ++ echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" ++ exit ;; + 5000:UNIX_System_V:4.*:*) +- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` +- FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` +- echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" ++ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` ++ FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` ++ echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" + exit ;; + i*86:BSD/386:*:* | i*86:BSD/OS:*:* | *:Ascend\ Embedded/OS:*:*) + echo ${UNAME_MACHINE}-pc-bsdi${UNAME_RELEASE} +@@ -792,13 +790,12 @@ EOF + echo ${UNAME_MACHINE}-unknown-bsdi${UNAME_RELEASE} + exit ;; + *:FreeBSD:*:*) +- case ${UNAME_MACHINE} in +- pc98) +- echo i386-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; ++ UNAME_PROCESSOR=`/usr/bin/uname -p` ++ case ${UNAME_PROCESSOR} in + amd64) + echo x86_64-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; + *) +- echo ${UNAME_MACHINE}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; ++ echo ${UNAME_PROCESSOR}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; + esac + exit ;; + i*:CYGWIN*:*) +@@ -807,19 +804,22 @@ EOF + *:MINGW*:*) + echo ${UNAME_MACHINE}-pc-mingw32 + exit ;; ++ i*:MSYS*:*) ++ echo ${UNAME_MACHINE}-pc-msys ++ exit ;; + i*:windows32*:*) +- # uname -m includes "-pc" on this system. +- echo ${UNAME_MACHINE}-mingw32 ++ # uname -m includes "-pc" on this system. ++ echo ${UNAME_MACHINE}-mingw32 + exit ;; + i*:PW*:*) + echo ${UNAME_MACHINE}-pc-pw32 + exit ;; +- *:Interix*:[3456]*) +- case ${UNAME_MACHINE} in ++ *:Interix*:*) ++ case ${UNAME_MACHINE} in + x86) + echo i586-pc-interix${UNAME_RELEASE} + exit ;; +- EM64T | authenticamd | genuineintel) ++ authenticamd | genuineintel | EM64T) + echo x86_64-unknown-interix${UNAME_RELEASE} + exit ;; + IA64) +@@ -829,6 +829,9 @@ EOF + [345]86:Windows_95:* | [345]86:Windows_98:* | [345]86:Windows_NT:*) + echo i${UNAME_MACHINE}-pc-mks + exit ;; ++ 8664:Windows_NT:*) ++ echo x86_64-pc-mks ++ exit ;; + i*:Windows_NT*:* | Pentium*:Windows_NT*:*) + # How do we know it's Interix rather than the generic POSIX subsystem? + # It also conflicts with pre-2.0 versions of AT&T UWIN. Should we +@@ -858,6 +861,27 @@ EOF + i*86:Minix:*:*) + echo ${UNAME_MACHINE}-pc-minix + exit ;; ++ aarch64:Linux:*:*) ++ echo ${UNAME_MACHINE}-unknown-linux-gnu ++ exit ;; ++ aarch64_be:Linux:*:*) ++ UNAME_MACHINE=aarch64_be ++ echo ${UNAME_MACHINE}-unknown-linux-gnu ++ exit ;; ++ alpha:Linux:*:*) ++ case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in ++ EV5) UNAME_MACHINE=alphaev5 ;; ++ EV56) UNAME_MACHINE=alphaev56 ;; ++ PCA56) UNAME_MACHINE=alphapca56 ;; ++ PCA57) UNAME_MACHINE=alphapca56 ;; ++ EV6) UNAME_MACHINE=alphaev6 ;; ++ EV67) UNAME_MACHINE=alphaev67 ;; ++ EV68*) UNAME_MACHINE=alphaev68 ;; ++ esac ++ objdump --private-headers /bin/sh | grep -q ld.so.1 ++ if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi ++ echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} ++ exit ;; + arm*:Linux:*:*) + eval $set_cc_for_build + if echo __ARM_EABI__ | $CC_FOR_BUILD -E - 2>/dev/null \ +@@ -865,20 +889,40 @@ EOF + then + echo ${UNAME_MACHINE}-unknown-linux-gnu + else +- echo ${UNAME_MACHINE}-unknown-linux-gnueabi ++ if echo __ARM_PCS_VFP | $CC_FOR_BUILD -E - 2>/dev/null \ ++ | grep -q __ARM_PCS_VFP ++ then ++ echo ${UNAME_MACHINE}-unknown-linux-gnueabi ++ else ++ echo ${UNAME_MACHINE}-unknown-linux-gnueabihf ++ fi + fi + exit ;; + avr32*:Linux:*:*) + echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; + cris:Linux:*:*) +- echo cris-axis-linux-gnu ++ echo ${UNAME_MACHINE}-axis-linux-gnu + exit ;; + crisv32:Linux:*:*) +- echo crisv32-axis-linux-gnu ++ echo ${UNAME_MACHINE}-axis-linux-gnu + exit ;; + frv:Linux:*:*) +- echo frv-unknown-linux-gnu ++ echo ${UNAME_MACHINE}-unknown-linux-gnu ++ exit ;; ++ hexagon:Linux:*:*) ++ echo ${UNAME_MACHINE}-unknown-linux-gnu ++ exit ;; ++ i*86:Linux:*:*) ++ LIBC=gnu ++ eval $set_cc_for_build ++ sed 's/^ //' << EOF >$dummy.c ++ #ifdef __dietlibc__ ++ LIBC=dietlibc ++ #endif ++EOF ++ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^LIBC'` ++ echo "${UNAME_MACHINE}-pc-linux-${LIBC}" + exit ;; + ia64:Linux:*:*) + echo ${UNAME_MACHINE}-unknown-linux-gnu +@@ -889,78 +933,34 @@ EOF + m68*:Linux:*:*) + echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; +- mips:Linux:*:*) +- eval $set_cc_for_build +- sed 's/^ //' << EOF >$dummy.c +- #undef CPU +- #undef mips +- #undef mipsel +- #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) +- CPU=mipsel +- #else +- #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) +- CPU=mips +- #else +- CPU= +- #endif +- #endif +-EOF +- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' +- /^CPU/{ +- s: ::g +- p +- }'`" +- test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } +- ;; +- mips64:Linux:*:*) ++ mips:Linux:*:* | mips64:Linux:*:*) + eval $set_cc_for_build + sed 's/^ //' << EOF >$dummy.c + #undef CPU +- #undef mips64 +- #undef mips64el ++ #undef ${UNAME_MACHINE} ++ #undef ${UNAME_MACHINE}el + #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) +- CPU=mips64el ++ CPU=${UNAME_MACHINE}el + #else + #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) +- CPU=mips64 ++ CPU=${UNAME_MACHINE} + #else + CPU= + #endif + #endif + EOF +- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' +- /^CPU/{ +- s: ::g +- p +- }'`" ++ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^CPU'` + test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } + ;; + or32:Linux:*:*) +- echo or32-unknown-linux-gnu +- exit ;; +- ppc:Linux:*:*) +- echo powerpc-unknown-linux-gnu +- exit ;; +- ppc64:Linux:*:*) +- echo powerpc64-unknown-linux-gnu +- exit ;; +- alpha:Linux:*:*) +- case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in +- EV5) UNAME_MACHINE=alphaev5 ;; +- EV56) UNAME_MACHINE=alphaev56 ;; +- PCA56) UNAME_MACHINE=alphapca56 ;; +- PCA57) UNAME_MACHINE=alphapca56 ;; +- EV6) UNAME_MACHINE=alphaev6 ;; +- EV67) UNAME_MACHINE=alphaev67 ;; +- EV68*) UNAME_MACHINE=alphaev68 ;; +- esac +- objdump --private-headers /bin/sh | grep ld.so.1 >/dev/null +- if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi +- echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} ++ echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; + padre:Linux:*:*) + echo sparc-unknown-linux-gnu + exit ;; ++ parisc64:Linux:*:* | hppa64:Linux:*:*) ++ echo hppa64-unknown-linux-gnu ++ exit ;; + parisc:Linux:*:* | hppa:Linux:*:*) + # Look for CPU level + case `grep '^cpu[^a-z]*:' /proc/cpuinfo 2>/dev/null | cut -d' ' -f2` in +@@ -969,14 +969,17 @@ EOF + *) echo hppa-unknown-linux-gnu ;; + esac + exit ;; +- parisc64:Linux:*:* | hppa64:Linux:*:*) +- echo hppa64-unknown-linux-gnu ++ ppc64:Linux:*:*) ++ echo powerpc64-unknown-linux-gnu ++ exit ;; ++ ppc:Linux:*:*) ++ echo powerpc-unknown-linux-gnu + exit ;; + s390:Linux:*:* | s390x:Linux:*:*) + echo ${UNAME_MACHINE}-ibm-linux + exit ;; + sh64*:Linux:*:*) +- echo ${UNAME_MACHINE}-unknown-linux-gnu ++ echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; + sh*:Linux:*:*) + echo ${UNAME_MACHINE}-unknown-linux-gnu +@@ -984,75 +987,18 @@ EOF + sparc:Linux:*:* | sparc64:Linux:*:*) + echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; ++ tile*:Linux:*:*) ++ echo ${UNAME_MACHINE}-unknown-linux-gnu ++ exit ;; + vax:Linux:*:*) + echo ${UNAME_MACHINE}-dec-linux-gnu + exit ;; + x86_64:Linux:*:*) +- echo x86_64-unknown-linux-gnu ++ echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; + xtensa*:Linux:*:*) +- echo ${UNAME_MACHINE}-unknown-linux-gnu ++ echo ${UNAME_MACHINE}-unknown-linux-gnu + exit ;; +- i*86:Linux:*:*) +- # The BFD linker knows what the default object file format is, so +- # first see if it will tell us. cd to the root directory to prevent +- # problems with other programs or directories called `ld' in the path. +- # Set LC_ALL=C to ensure ld outputs messages in English. +- ld_supported_targets=`cd /; LC_ALL=C ld --help 2>&1 \ +- | sed -ne '/supported targets:/!d +- s/[ ][ ]*/ /g +- s/.*supported targets: *// +- s/ .*// +- p'` +- case "$ld_supported_targets" in +- elf32-i386) +- TENTATIVE="${UNAME_MACHINE}-pc-linux-gnu" +- ;; +- a.out-i386-linux) +- echo "${UNAME_MACHINE}-pc-linux-gnuaout" +- exit ;; +- "") +- # Either a pre-BFD a.out linker (linux-gnuoldld) or +- # one that does not give us useful --help. +- echo "${UNAME_MACHINE}-pc-linux-gnuoldld" +- exit ;; +- esac +- # Determine whether the default compiler is a.out or elf +- eval $set_cc_for_build +- sed 's/^ //' << EOF >$dummy.c +- #include +- #ifdef __ELF__ +- # ifdef __GLIBC__ +- # if __GLIBC__ >= 2 +- LIBC=gnu +- # else +- LIBC=gnulibc1 +- # endif +- # else +- LIBC=gnulibc1 +- # endif +- #else +- #if defined(__INTEL_COMPILER) || defined(__PGI) || defined(__SUNPRO_C) || defined(__SUNPRO_CC) +- LIBC=gnu +- #else +- LIBC=gnuaout +- #endif +- #endif +- #ifdef __dietlibc__ +- LIBC=dietlibc +- #endif +-EOF +- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' +- /^LIBC/{ +- s: ::g +- p +- }'`" +- test x"${LIBC}" != x && { +- echo "${UNAME_MACHINE}-pc-linux-${LIBC}" +- exit +- } +- test x"${TENTATIVE}" != x && { echo "${TENTATIVE}"; exit; } +- ;; + i*86:DYNIX/ptx:4*:*) + # ptx 4.0 does uname -s correctly, with DYNIX/ptx in there. + # earlier versions are messed up and put the nodename in both +@@ -1060,11 +1006,11 @@ EOF + echo i386-sequent-sysv4 + exit ;; + i*86:UNIX_SV:4.2MP:2.*) +- # Unixware is an offshoot of SVR4, but it has its own version +- # number series starting with 2... +- # I am not positive that other SVR4 systems won't match this, ++ # Unixware is an offshoot of SVR4, but it has its own version ++ # number series starting with 2... ++ # I am not positive that other SVR4 systems won't match this, + # I just have to hope. -- rms. +- # Use sysv4.2uw... so that sysv4* matches it. ++ # Use sysv4.2uw... so that sysv4* matches it. + echo ${UNAME_MACHINE}-pc-sysv4.2uw${UNAME_VERSION} + exit ;; + i*86:OS/2:*:*) +@@ -1081,7 +1027,7 @@ EOF + i*86:syllable:*:*) + echo ${UNAME_MACHINE}-pc-syllable + exit ;; +- i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.0*:*) ++ i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.[02]*:*) + echo i386-unknown-lynxos${UNAME_RELEASE} + exit ;; + i*86:*DOS:*:*) +@@ -1096,7 +1042,7 @@ EOF + fi + exit ;; + i*86:*:5:[678]*) +- # UnixWare 7.x, OpenUNIX and OpenServer 6. ++ # UnixWare 7.x, OpenUNIX and OpenServer 6. + case `/bin/uname -X | grep "^Machine"` in + *486*) UNAME_MACHINE=i486 ;; + *Pentium) UNAME_MACHINE=i586 ;; +@@ -1124,10 +1070,13 @@ EOF + exit ;; + pc:*:*:*) + # Left here for compatibility: +- # uname -m prints for DJGPP always 'pc', but it prints nothing about +- # the processor, so we play safe by assuming i386. +- echo i386-pc-msdosdjgpp +- exit ;; ++ # uname -m prints for DJGPP always 'pc', but it prints nothing about ++ # the processor, so we play safe by assuming i586. ++ # Note: whatever this is, it MUST be the same as what config.sub ++ # prints for the "djgpp" host, or else GDB configury will decide that ++ # this is a cross-build. ++ echo i586-pc-msdosdjgpp ++ exit ;; + Intel:Mach:3*:*) + echo i386-pc-mach3 + exit ;; +@@ -1162,8 +1111,18 @@ EOF + /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ + && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; + 3[34]??:*:4.0:* | 3[34]??,*:*:4.0:*) +- /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ +- && { echo i486-ncr-sysv4; exit; } ;; ++ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ ++ && { echo i486-ncr-sysv4; exit; } ;; ++ NCR*:*:4.2:* | MPRAS*:*:4.2:*) ++ OS_REL='.3' ++ test -r /etc/.relid \ ++ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` ++ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ ++ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } ++ /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ ++ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ++ /bin/uname -p 2>/dev/null | /bin/grep pteron >/dev/null \ ++ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; + m68*:LynxOS:2.*:* | m68*:LynxOS:3.0*:*) + echo m68k-unknown-lynxos${UNAME_RELEASE} + exit ;; +@@ -1176,7 +1135,7 @@ EOF + rs6000:LynxOS:2.*:*) + echo rs6000-unknown-lynxos${UNAME_RELEASE} + exit ;; +- PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.0*:*) ++ PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.[02]*:*) + echo powerpc-unknown-lynxos${UNAME_RELEASE} + exit ;; + SM[BE]S:UNIX_SV:*:*) +@@ -1196,10 +1155,10 @@ EOF + echo ns32k-sni-sysv + fi + exit ;; +- PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort +- # says +- echo i586-unisys-sysv4 +- exit ;; ++ PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort ++ # says ++ echo i586-unisys-sysv4 ++ exit ;; + *:UNIX_System_V:4*:FTX*) + # From Gerald Hewes . + # How about differentiating between stratus architectures? -djm +@@ -1225,11 +1184,11 @@ EOF + exit ;; + R[34]000:*System_V*:*:* | R4000:UNIX_SYSV:*:* | R*000:UNIX_SV:*:*) + if [ -d /usr/nec ]; then +- echo mips-nec-sysv${UNAME_RELEASE} ++ echo mips-nec-sysv${UNAME_RELEASE} + else +- echo mips-unknown-sysv${UNAME_RELEASE} ++ echo mips-unknown-sysv${UNAME_RELEASE} + fi +- exit ;; ++ exit ;; + BeBox:BeOS:*:*) # BeOS running on hardware made by Be, PPC only. + echo powerpc-be-beos + exit ;; +@@ -1269,6 +1228,16 @@ EOF + *:Darwin:*:*) + UNAME_PROCESSOR=`uname -p` || UNAME_PROCESSOR=unknown + case $UNAME_PROCESSOR in ++ i386) ++ eval $set_cc_for_build ++ if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then ++ if (echo '#ifdef __LP64__'; echo IS_64BIT_ARCH; echo '#endif') | \ ++ (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ ++ grep IS_64BIT_ARCH >/dev/null ++ then ++ UNAME_PROCESSOR="x86_64" ++ fi ++ fi ;; + unknown) UNAME_PROCESSOR=powerpc ;; + esac + echo ${UNAME_PROCESSOR}-apple-darwin${UNAME_RELEASE} +@@ -1284,6 +1253,9 @@ EOF + *:QNX:*:4*) + echo i386-pc-qnx + exit ;; ++ NEO-?:NONSTOP_KERNEL:*:*) ++ echo neo-tandem-nsk${UNAME_RELEASE} ++ exit ;; + NSE-?:NONSTOP_KERNEL:*:*) + echo nse-tandem-nsk${UNAME_RELEASE} + exit ;; +@@ -1329,13 +1301,13 @@ EOF + echo pdp10-unknown-its + exit ;; + SEI:*:*:SEIUX) +- echo mips-sei-seiux${UNAME_RELEASE} ++ echo mips-sei-seiux${UNAME_RELEASE} + exit ;; + *:DragonFly:*:*) + echo ${UNAME_MACHINE}-unknown-dragonfly`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` + exit ;; + *:*VMS:*:*) +- UNAME_MACHINE=`(uname -p) 2>/dev/null` ++ UNAME_MACHINE=`(uname -p) 2>/dev/null` + case "${UNAME_MACHINE}" in + A*) echo alpha-dec-vms ; exit ;; + I*) echo ia64-dec-vms ; exit ;; +@@ -1350,6 +1322,12 @@ EOF + i*86:rdos:*:*) + echo ${UNAME_MACHINE}-pc-rdos + exit ;; ++ i*86:AROS:*:*) ++ echo ${UNAME_MACHINE}-pc-aros ++ exit ;; ++ x86_64:VMkernel:*:*) ++ echo ${UNAME_MACHINE}-unknown-esx ++ exit ;; + esac + + #echo '(No uname command or uname output not recognized.)' 1>&2 +@@ -1372,11 +1350,11 @@ main () + #include + printf ("m68k-sony-newsos%s\n", + #ifdef NEWSOS4 +- "4" ++ "4" + #else +- "" ++ "" + #endif +- ); exit (0); ++ ); exit (0); + #endif + #endif + +diff --git a/configure.ac b/configure.ac +index 9237c77..8e3d9d2 100644 +--- a/configure.ac ++++ b/configure.ac +@@ -210,6 +210,20 @@ AC_CANONICAL_BUILD + AC_CANONICAL_HOST + AC_CANONICAL_TARGET + ++# Testing ARM ABI ++# required for code generation (LLVM options) ++ARM_ABI=SOFT ++echo HOST: $host ++ ++case $host in ++ arm*-*-linux-gnueabihf) ++ ARM_ABI=HARD ++ ;; ++ arm*-*-linux-gnueabi) ++ ARM_ABI=SOFTFP ++ ;; ++esac ++ + FPTOOLS_SET_PLATFORM_VARS + + # Verify that the installed (bootstrap) GHC is capable of generating +-- +1.7.4.3 + diff --git a/ghc-debian-ARM-VFPv3D16.patch b/ghc-debian-ARM-VFPv3D16.patch deleted file mode 100644 index ffe76cb..0000000 --- a/ghc-debian-ARM-VFPv3D16.patch +++ /dev/null @@ -1,16 +0,0 @@ -Description: Use VFPv3-D16 FPU for ARM builds -Author: Jani Monoses - -Index: ghc/aclocal.m4 -=================================================================== ---- ghc.orig/aclocal.m4 2012-02-01 18:10:32.000000000 +0000 -+++ ghc/aclocal.m4 2012-03-10 16:40:32.415005650 +0000 -@@ -333,7 +333,7 @@ - ], - [changequote(, )dnl - ARM_ISA=ARMv7 -- ARM_ISA_EXT="[VFPv3,NEON]" -+ ARM_ISA_EXT="[VFPv3D16,NEON]" - changequote([, ])dnl - ]) - ]) diff --git a/ghc-debian-armhf_llvm_abi.patch b/ghc-debian-armhf_llvm_abi.patch deleted file mode 100644 index c3b045e..0000000 --- a/ghc-debian-armhf_llvm_abi.patch +++ /dev/null @@ -1,26 +0,0 @@ -Description: If we are on armhf, tell llvm to generate code for this ABI. Not - forwarded upstream, because they will do a more 'proper' patch. See upstream - bug #5914. -Author: Iain Lane - -Index: ghc/compiler/main/DriverPipeline.hs -=================================================================== ---- ghc.orig/compiler/main/DriverPipeline.hs 2012-03-10 16:41:46.000000000 +0000 -+++ ghc/compiler/main/DriverPipeline.hs 2012-03-10 16:42:59.209169474 +0000 -@@ -1,5 +1,5 @@ - {-# OPTIONS -fno-cse #-} --{-# LANGUAGE NamedFieldPuns #-} -+{-# LANGUAGE NamedFieldPuns, CPP #-} - -- -fno-cse is needed for GLOBAL_VAR's to behave properly - - ----------------------------------------------------------------------------- -@@ -1379,6 +1379,9 @@ - then ["-mattr=+v7,+vfp3"] - else if (elem VFPv3D16 ext) - then ["-mattr=+v7,+vfp3,+d16"] -+#ifdef __ARM_PCS_VFP -+ ++ ["-float-abi=hard"] -+#endif - else [] - _ -> [] - diff --git a/ghc.spec b/ghc.spec index 6ae21bd..70d797f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_hscolour 1 -#%%global without_testsuite 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_hscolour 1 +%global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -25,12 +25,12 @@ Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.4.1 +Version: 7.4.2 # Since library subpackages are versioned: # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 6%{?dist} +Release: 7%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -98,12 +98,8 @@ Patch8: ghc-powerpc-linker-mmap.patch Patch9: Cabal-fix-dynamic-exec-for-TH.patch # add libffi include dir to ghc wrapper for archs using gcc/llc Patch10: ghc-wrapper-libffi-include.patch -# Debian armel fixes -Patch11: fix-ARM-s-StgCRun-clobbered-register-list-for-both-A.patch -Patch12: fix-ARM-StgCRun-to-not-save-and-restore-r11-fp-regis.patch -# Debian armhf fixes -Patch13: ghc-debian-ARM-VFPv3D16.patch -Patch14: ghc-debian-armhf_llvm_abi.patch +# latest arm hf patch +Patch11: ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -159,7 +155,7 @@ To install all of ghc, install the ghc base package. %if %{defined ghclibdir} %ghc_lib_subpackage Cabal 1.14.0 %ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.1.0 %ghc_lib_subpackage binary 0.5.1.0 %ghc_lib_subpackage bytestring 0.9.2.1 %ghc_lib_subpackage -l %BSDHaskellReport containers 0.4.2.1 @@ -181,7 +177,7 @@ To install all of ghc, install the ghc base package. %ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.1 %ghc_lib_subpackage template-haskell 2.7.0.0 %ghc_lib_subpackage time 1.4 -%ghc_lib_subpackage unix 2.5.1.0 +%ghc_lib_subpackage unix 2.5.1.1 %endif %global version %{ghc_version_override} @@ -224,14 +220,9 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %endif # ARM patches -%ifarch armv7hl armv5tel -%patch11 -p1 -b .arm1 -%patch12 -p1 -b .arm2 -%endif %ifarch armv7hl # touches aclocal.m4 -%patch13 -p1 -b .arm -%patch14 -p1 -b .arm +%patch11 -p1 -b .arm autoreconf %endif @@ -249,9 +240,6 @@ BUILD_DOCBOOK_HTML = NO %if %{undefined without_hscolour} HSCOLOUR_SRCS = NO %endif -%ifarch armv7hl -SRC_HC_OPTS += -D__ARM_PCS_VFP -%endif EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -263,10 +251,7 @@ export CFLAGS="${CFLAGS:-%optflags}" --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --with-gcc=%{_bindir}/gcc -# >4 cpus tends to break build -[ -z "$RPM_BUILD_NCPUS" ] && RPM_BUILD_NCPUS=$(%{_bindir}/getconf _NPROCESSORS_ONLN) -[ "$RPM_BUILD_NCPUS" -gt 4 ] && RPM_BUILD_NCPUS=4 -make -j$RPM_BUILD_NCPUS +make %{?_smp_mflags} %install make DESTDIR=${RPM_BUILD_ROOT} install @@ -435,6 +420,14 @@ fi %files libraries %changelog +* Fri Aug 24 2012 Jens Petersen - 7.4.2-7 +- 7.4.2 bootstrap + http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html +- update base and unix library versions +- ARM StgCRun patches not longer needed +- use Karel Gardas' ARM hardfloat patch committed upstream +- use _smp_mflags again + * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild diff --git a/sources b/sources index 1013c18..f54a493 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -54bc9405c14c3226b6e3de3cd61e2777 ghc-7.4.1-testsuite.tar.bz2 -5d86c420978b49cc60edea9bd4c36703 ghc-7.4.1-src.tar.bz2 +528005749c761fe6c12a0079bd84fb90 ghc-7.4.2-testsuite.tar.bz2 From 23a67a6190a4d43475e8be402dea7dacf04d68d6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Aug 2012 21:33:48 +0900 Subject: [PATCH 331/530] disable Cabal building ghci lib files --- ghc-7.4.2-Cabal-disable-ghci-libs.patch | 13 +++++++++++++ ghc.spec | 5 +++++ 2 files changed, 18 insertions(+) create mode 100644 ghc-7.4.2-Cabal-disable-ghci-libs.patch diff --git a/ghc-7.4.2-Cabal-disable-ghci-libs.patch b/ghc-7.4.2-Cabal-disable-ghci-libs.patch new file mode 100644 index 0000000..cdefe0d --- /dev/null +++ b/ghc-7.4.2-Cabal-disable-ghci-libs.patch @@ -0,0 +1,13 @@ +--- ghc-7.4.2/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs~ 2012-06-07 02:10:40.000000000 +0900 ++++ ghc-7.4.2/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs 2012-08-24 20:33:00.032123967 +0900 +@@ -313,7 +313,7 @@ + configDistPref = Flag defaultDistPref, + configVerbosity = Flag normal, + configUserInstall = Flag False, --TODO: reverse this +- configGHCiLib = Flag True, ++ configGHCiLib = Flag False, + configSplitObjs = Flag False, -- takes longer, so turn off by default + configStripExes = Flag True, + configTests = Flag False, + +Diff finished. Fri Aug 24 20:33:10 2012 diff --git a/ghc.spec b/ghc.spec index 70d797f..cdc060d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -100,6 +100,8 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch Patch10: ghc-wrapper-libffi-include.patch # latest arm hf patch Patch11: ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch +# disable building HS*.o libs for ghci +Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -226,6 +228,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build autoreconf %endif +%patch12 -p1 -b .orig + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -427,6 +431,7 @@ fi - ARM StgCRun patches not longer needed - use Karel Gardas' ARM hardfloat patch committed upstream - use _smp_mflags again +- disable Cabal building ghci lib files * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From 24f8205758c0e09b7ed87aa42b56bd853b480f8b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 29 Aug 2012 19:17:04 +0900 Subject: [PATCH 332/530] really add ghc-7.4.2-src.tar.bz2 --- sources | 1 + 1 file changed, 1 insertion(+) diff --git a/sources b/sources index f54a493..46b12d9 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ +267462db5c5a7c245fb26361b77007c4 ghc-7.4.2-src.tar.bz2 528005749c761fe6c12a0079bd84fb90 ghc-7.4.2-testsuite.tar.bz2 From b9b8245f7ae12b558c92ff7aa64f122634af516b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 30 Sep 2012 17:52:34 +0900 Subject: [PATCH 333/530] use %buildroot instead of $RPM_BUILD_ROOT ; remove HS*.o files --- ghc.spec | 28 ++++++++++++++++------------ 1 file changed, 16 insertions(+), 12 deletions(-) diff --git a/ghc.spec b/ghc.spec index cdc060d..050a5ba 100644 --- a/ghc.spec +++ b/ghc.spec @@ -258,7 +258,10 @@ export CFLAGS="${CFLAGS:-%optflags}" make %{?_smp_mflags} %install -make DESTDIR=${RPM_BUILD_ROOT} install +make DESTDIR=%{buildroot} install + +# this should be done in the buildsys +find %{buildroot} -type f -name "HS*.o" -delete for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") @@ -285,28 +288,28 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist bin-package-db ghc %if %{undefined ghc_without_shared} -ls $RPM_BUILD_ROOT%{ghclibdir}/libHS*.so >> ghc-base.files -sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base.files +ls %{buildroot}%{ghclibdir}/libHS*.so >> ghc-base.files +sed -i -e "s|^%{buildroot}||g" ghc-base.files %endif -ls -d $RPM_BUILD_ROOT%{ghclibdir}/libHS*.a $RPM_BUILD_ROOT%{ghclibdir}/package.conf.d/builtin_*.conf $RPM_BUILD_ROOT%{ghclibdir}/include >> ghc-base-devel.files -sed -i -e "s|^$RPM_BUILD_ROOT||g" ghc-base-devel.files +ls -d %{buildroot}%{ghclibdir}/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files +sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files # these are handled as alternatives for i in hsc2hs runhaskell; do - if [ -x ${RPM_BUILD_ROOT}%{_bindir}/$i-ghc ]; then - rm ${RPM_BUILD_ROOT}%{_bindir}/$i + if [ -x %{buildroot}%{_bindir}/$i-ghc ]; then + rm %{buildroot}%{_bindir}/$i else - mv ${RPM_BUILD_ROOT}%{_bindir}/$i{,-ghc} + mv %{buildroot}%{_bindir}/$i{,-ghc} fi - touch ${RPM_BUILD_ROOT}%{_bindir}/$i + touch %{buildroot}%{_bindir}/$i done %ghc_strip_dynlinked %if %{undefined without_haddock} -mkdir -p ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly -install -p --mode=755 %SOURCE3 ${RPM_BUILD_ROOT}%{_sysconfdir}/cron.hourly/ghc-doc-index -mkdir -p ${RPM_BUILD_ROOT}%{_localstatedir}/lib/ghc +mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly +install -p --mode=755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index +mkdir -p %{buildroot}%{_localstatedir}/lib/ghc %endif %check @@ -432,6 +435,7 @@ fi - use Karel Gardas' ARM hardfloat patch committed upstream - use _smp_mflags again - disable Cabal building ghci lib files +- forcibly remove HS*.o files from ghc libs for now * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From d536f17acf5b51ba80ef078b138587b73daec95e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Oct 2012 14:00:31 +0900 Subject: [PATCH 334/530] revert the removal of ghci HS*.o lib files (see http://hackage.haskell.org/trac/ghc/ticket/7249) --- ghc.spec | 4 ---- 1 file changed, 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 050a5ba..41898bd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -260,9 +260,6 @@ make %{?_smp_mflags} %install make DESTDIR=%{buildroot} install -# this should be done in the buildsys -find %{buildroot} -type f -name "HS*.o" -delete - for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") @@ -435,7 +432,6 @@ fi - use Karel Gardas' ARM hardfloat patch committed upstream - use _smp_mflags again - disable Cabal building ghci lib files -- forcibly remove HS*.o files from ghc libs for now * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From 7eeada86246ef3745aad454fda4edb54dfae0175 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 25 Oct 2012 16:49:08 +0900 Subject: [PATCH 335/530] enable hscolour normally, drop BR hscolour, without_hscolour bootstrap now in ghc-rpm-macros --- ghc.spec | 13 ++++--------- 1 file changed, 4 insertions(+), 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 41898bd..cb4f958 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,16 +1,14 @@ # Shared haskell libraries are supported for x86* archs # (disabled for other archs in ghc-rpm-macros) -# To bootstrap a new version of ghc, uncomment the following: +# To bootstrap build a new version of ghc, uncomment the following: %global ghc_bootstrapping 1 %{?ghc_bootstrap} -%global without_hscolour 1 %global without_testsuite 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 #%%{?ghc_test} -#%%global without_hscolour 1 #%%global without_testsuite 1 # unregisterized archs @@ -68,9 +66,6 @@ BuildRequires: ncurses-devel %if %{undefined without_manual} BuildRequires: libxslt, docbook-style-xsl %endif -%if %{undefined without_haddock} && %{undefined without_hscolour} -BuildRequires: hscolour -%endif %if %{undefined without_testsuite} BuildRequires: python %endif @@ -241,9 +236,6 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif -%if %{undefined without_hscolour} -HSCOLOUR_SRCS = NO -%endif EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -432,6 +424,9 @@ fi - use Karel Gardas' ARM hardfloat patch committed upstream - use _smp_mflags again - disable Cabal building ghci lib files +- do not disable hscolour in build.mk +- drop the explicit hscolour BR +- without_hscolour should now be set by ghc-rpm-macros for bootstrapping * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From b2f2d6c05a7cbd9b16c943f52fd56406e3a32131 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 29 Oct 2012 20:14:11 +0900 Subject: [PATCH 336/530] drop doc re-indexing cronjob and add a rpm-state dir for posttrans scripts (#870694) --- ghc-doc-index.cron | 41 ------------------------- ghc-gen_contents_index-cron-batch.patch | 20 ------------ ghc.spec | 17 +++++----- 3 files changed, 7 insertions(+), 71 deletions(-) delete mode 100755 ghc-doc-index.cron delete mode 100644 ghc-gen_contents_index-cron-batch.patch diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron deleted file mode 100755 index 9cf2888..0000000 --- a/ghc-doc-index.cron +++ /dev/null @@ -1,41 +0,0 @@ -#! /bin/bash - -if [ -e /etc/sysconfig/ghc-doc-index ]; then - . /etc/sysconfig/ghc-doc-index -fi - -if [ "$CRON" = "no" ]; then - exit 0 -fi - - -LOCKFILE=/var/lock/ghc-doc-index.lock - -# the lockfile is not meant to be perfect, it's just in case the -# two cron scripts get run close to each other to keep -# them from stepping on each other's toes. -[ -f $LOCKFILE ] && exit 0 - -trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT -touch $LOCKFILE - -PKGDIRCACHE=/var/lib/ghc/pkg-dir.cache -LISTING="env LANG=C ls -dl" - -# only re-index ghc docs when there are changes -cd /usr/share/doc/ghc/html/libraries -if [ -r "$PKGDIRCACHE" ]; then - $LISTING */ > $PKGDIRCACHE.new - DIR_DIFF=$(diff $PKGDIRCACHE $PKGDIRCACHE.new) -else - $LISTING */ > $PKGDIRCACHE -fi -if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; then - ./gen_contents_index --batch -fi - -if [ -f $PKGDIRCACHE.new ]; then - mv -f $PKGDIRCACHE{.new,} -fi - -exit 0 diff --git a/ghc-gen_contents_index-cron-batch.patch b/ghc-gen_contents_index-cron-batch.patch deleted file mode 100644 index 9e30974..0000000 --- a/ghc-gen_contents_index-cron-batch.patch +++ /dev/null @@ -1,20 +0,0 @@ -diff -u ghc-6.12.3/libraries/gen_contents_index gen_contents_index ---- ghc-6.12.3/libraries/gen_contents_index 2010-11-05 10:28:02.000000000 +1000 -+++ gen_contents_index 2010-11-05 10:20:37.000000000 +1000 -@@ -22,5 +22,5 @@ - done - ;; --*) -+--batch) - HADDOCK=/usr/bin/haddock - # We don't want the GHC API to swamp the index -@@ -32,6 +32,9 @@ - HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" - done - ;; -+*) -+ HADDOCK=/bin/true -+ tty -s && echo Run with '--batch' to index package haddock docs. - esac - - # Now create the combined contents and index pages diff --git a/ghc.spec b/ghc.spec index cb4f958..693ed3b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -40,7 +40,6 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif -Source3: ghc-doc-index.cron URL: http://haskell.org/ghc/ Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 @@ -82,8 +81,6 @@ Requires: ghc-ghc-devel = %{version}-%{release} Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch # type-level too big so skip it in gen_contents_index Patch2: ghc-gen_contents_index-type-level.patch -# disable gen_contents_index when not --batch for cron -Patch3: ghc-gen_contents_index-cron-batch.patch # fedora does not allow copy libraries Patch4: ghc-use-system-libffi.patch Patch7: ghc-powerpc-pthread.patch @@ -200,7 +197,6 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} %patch1 -p1 -b .orig %patch2 -p1 -%patch3 -p1 # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -296,11 +292,10 @@ done %ghc_strip_dynlinked %if %{undefined without_haddock} -mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly -install -p --mode=755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index -mkdir -p %{buildroot}%{_localstatedir}/lib/ghc +mkdir -p %{buildroot}%{_localstatedir}/lib/rpm-state/ghc %endif + %check # stolen from ghc6/debian/rules: # Do some very simple tests that the compiler actually works @@ -409,14 +404,13 @@ fi %ghost %{ghcdocbasedir}/libraries/index*.html %ghost %{ghcdocbasedir}/libraries/minus.gif %ghost %{ghcdocbasedir}/libraries/plus.gif -%{_sysconfdir}/cron.hourly/ghc-doc-index -%{_localstatedir}/lib/ghc +%{_localstatedir}/lib/rpm-state/ghc %endif %files libraries %changelog -* Fri Aug 24 2012 Jens Petersen - 7.4.2-7 +* Mon Oct 29 2012 Jens Petersen - 7.4.2-7 - 7.4.2 bootstrap http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html - update base and unix library versions @@ -427,6 +421,9 @@ fi - do not disable hscolour in build.mk - drop the explicit hscolour BR - without_hscolour should now be set by ghc-rpm-macros for bootstrapping +- drop cronjob for re-indexing html docs and add a rpm-state dir for + sharing state between devel posttrans scripts (#870694) + (http://fedoraproject.org/wiki/Packaging:ScriptletSnippets#Saving_state_between_scriptlets) * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From 1456df9b18a8d9aacca528960cff352e0862d470 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 16 Nov 2012 16:57:46 +0900 Subject: [PATCH 337/530] revert rpm-state and bring back ghc-doc-index cronjob in ghc-doc-index subpackage - add new ghc-doc-index script - forward port ghc-7.4-silence-gen_contents_index.patch - remove /var/lib/rpm-state/ghc/ --- ghc-7.4-silence-gen_contents_index.patch | 11 ++++++++ ghc-doc-index | 33 ++++++++++++++++++++++++ ghc-doc-index.cron | 13 ++++++++++ ghc.spec | 25 +++++++++++++----- 4 files changed, 76 insertions(+), 6 deletions(-) create mode 100644 ghc-7.4-silence-gen_contents_index.patch create mode 100644 ghc-doc-index create mode 100755 ghc-doc-index.cron diff --git a/ghc-7.4-silence-gen_contents_index.patch b/ghc-7.4-silence-gen_contents_index.patch new file mode 100644 index 0000000..d000b8b --- /dev/null +++ b/ghc-7.4-silence-gen_contents_index.patch @@ -0,0 +1,11 @@ +--- ghc-7.4.1/libraries/gen_contents_index~ 2012-09-30 16:14:39.368295240 +0900 ++++ ghc-7.4.1/libraries/gen_contents_index 2012-10-30 19:12:10.017398594 +0900 +@@ -50,7 +50,7 @@ + esac + + # Now create the combined contents and index pages +-echo $HADDOCK_ARGS ++#echo $HADDOCK_ARGS + $HADDOCK --gen-index --gen-contents -o . \ + -t "Haskell Hierarchical Libraries" \ + -p "prologue.txt" \ diff --git a/ghc-doc-index b/ghc-doc-index new file mode 100644 index 0000000..eca75f1 --- /dev/null +++ b/ghc-doc-index @@ -0,0 +1,33 @@ +#!/bin/sh + +LOCKFILE=/var/lock/ghc-doc-index.lock + +# the lockfile is not meant to be perfect, it's just in case +# two cron scripts get run close to each other to keep +# them from stepping on each other's toes. +if [ -f $LOCKFILE ]; then + echo "Locked with $LOCKFILE" + exit 0 +fi + +trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT +touch $LOCKFILE + +PKGDIRCACHE=/var/lib/ghc/pkg-dir.cache +LISTING="env LANG=C ls -dl" + +# only re-index ghc docs when there are changes +cd /usr/share/doc/ghc/html/libraries +if [ -r "$PKGDIRCACHE" ]; then + $LISTING */ > $PKGDIRCACHE.new + DIR_DIFF=$(diff $PKGDIRCACHE $PKGDIRCACHE.new) +else + $LISTING */ > $PKGDIRCACHE +fi +if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; then + ./gen_contents_index +fi + +if [ -f $PKGDIRCACHE.new ]; then + mv -f $PKGDIRCACHE{.new,} +fi diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron new file mode 100755 index 0000000..e353689 --- /dev/null +++ b/ghc-doc-index.cron @@ -0,0 +1,13 @@ +#! /bin/bash + +if [ -e /etc/sysconfig/ghc-doc-index ]; then + . /etc/sysconfig/ghc-doc-index +fi + +if [ "$CRON" = "no" ]; then + exit 0 +fi + +/usr/bin/ghc-doc-index >/dev/null + +exit 0 diff --git a/ghc.spec b/ghc.spec index 693ed3b..9a9cdfa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -40,6 +40,8 @@ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif +Source3: ghc-doc-index.cron +Source4: ghc-doc-index URL: http://haskell.org/ghc/ Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 @@ -75,6 +77,7 @@ BuildRequires: llvm >= 3.0 BuildRequires: autoconf %endif Requires: ghc-compiler = %{version}-%{release} +Requires: ghc-doc-index = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} # absolute haddock path (was for html/libraries -> libraries) @@ -94,6 +97,7 @@ Patch10: ghc-wrapper-libffi-include.patch Patch11: ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch # disable building HS*.o libs for ghci Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch +Patch17: ghc-7.4-silence-gen_contents_index.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -195,8 +199,11 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} + +# tweaks to gen_contents_index %patch1 -p1 -b .orig %patch2 -p1 +%patch17 -p1 # make sure we don't use these rm -r ghc-tarballs/{mingw,perl} @@ -292,10 +299,11 @@ done %ghc_strip_dynlinked %if %{undefined without_haddock} -mkdir -p %{buildroot}%{_localstatedir}/lib/rpm-state/ghc +mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly +install -p --mode=755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index +mkdir -p %{buildroot}%{_localstatedir}/lib/ghc %endif - %check # stolen from ghc6/debian/rules: # Do some very simple tests that the compiler actually works @@ -351,6 +359,7 @@ fi %doc ANNOUNCE HACKING LICENSE README %{_bindir}/ghc %{_bindir}/ghc-%{version} +%{_bindir}/ghc-doc-index %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} %{_bindir}/ghci @@ -404,7 +413,12 @@ fi %ghost %{ghcdocbasedir}/libraries/index*.html %ghost %{ghcdocbasedir}/libraries/minus.gif %ghost %{ghcdocbasedir}/libraries/plus.gif -%{_localstatedir}/lib/rpm-state/ghc +%{_localstatedir}/lib/ghc +%endif + +%if %{undefined without_haddock} +%files doc-index +%{_sysconfdir}/cron.hourly/ghc-doc-index %endif %files libraries @@ -418,12 +432,11 @@ fi - use Karel Gardas' ARM hardfloat patch committed upstream - use _smp_mflags again - disable Cabal building ghci lib files +- silence the doc re-indexing script and move the doc indexing cronjob + to a new ghc-doc-index subpackage (#870694) - do not disable hscolour in build.mk - drop the explicit hscolour BR - without_hscolour should now be set by ghc-rpm-macros for bootstrapping -- drop cronjob for re-indexing html docs and add a rpm-state dir for - sharing state between devel posttrans scripts (#870694) - (http://fedoraproject.org/wiki/Packaging:ScriptletSnippets#Saving_state_between_scriptlets) * Thu Jul 19 2012 Fedora Release Engineering - 7.4.1-6 - Rebuilt for https://fedoraproject.org/wiki/Fedora_18_Mass_Rebuild From bf18859b4e913bc3e26499c630a44d28b88f55ce Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Nov 2012 12:28:31 +0900 Subject: [PATCH 338/530] update changelog timestamp --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 9a9cdfa..f1a1640 100644 --- a/ghc.spec +++ b/ghc.spec @@ -424,7 +424,7 @@ fi %files libraries %changelog -* Mon Oct 29 2012 Jens Petersen - 7.4.2-7 +* Sat Nov 17 2012 Jens Petersen - 7.4.2-7 - 7.4.2 bootstrap http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html - update base and unix library versions From 2ccedef175dd729d32500fb35c19704a4bc77468 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Nov 2012 18:43:22 +0900 Subject: [PATCH 339/530] define doc-index subpackage and set without_haddock for bootstrap - drop Group fields --- ghc.spec | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index f1a1640..bdfedb2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -5,6 +5,7 @@ %global ghc_bootstrapping 1 %{?ghc_bootstrap} %global without_testsuite 1 +%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -35,7 +36,6 @@ Summary: Glasgow Haskell Compiler # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros ExcludeArch: sparc64 License: %BSDHaskellReport -Group: Development/Languages Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 @@ -122,7 +122,6 @@ for the functional language Haskell. Highlights: %package compiler Summary: GHC compiler and utilities License: BSD -Group: Development/Languages Requires: gcc%{?_isa} Requires: ghc-base-devel%{?_isa} # for alternatives @@ -140,6 +139,17 @@ The package contains the GHC compiler, tools and utilities. The ghc libraries are provided by ghc-devel. To install all of ghc, install the ghc base package. +%if %{undefined without_haddock} +%package doc-index +Summary: GHC library development documentation indexing +License: BSD +Requires: ghc-compiler = %{version}-%{release} + +%description doc-index +The package provides a cronjob for re-indexing installed library development +documention. +%endif + %global ghc_version_override %{version} # needs ghc_version_override for bootstrapping @@ -183,7 +193,6 @@ To install all of ghc, install the ghc base package. %package libraries Summary: GHC development libraries meta package License: %BSDHaskellReport -Group: Development/Libraries Requires: ghc-compiler = %{version}-%{release} Obsoletes: ghc-devel < %{version}-%{release} Provides: ghc-devel = %{version}-%{release} From 3d6c74cbb088c44978f434d33b5f3c66ebc6c18a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Nov 2012 20:35:05 +0900 Subject: [PATCH 340/530] "bogus date in %changelog: Tue Dec 12 2007" --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index bdfedb2..50454c4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1015,7 +1015,7 @@ fi * Sun Jan 06 2008 Bryan O'Sullivan - 6.8.2-6 - Fix docdir -* Tue Dec 12 2007 Bryan O'Sullivan - 6.8.2-1 +* Wed Dec 12 2007 Bryan O'Sullivan - 6.8.2-1 - Update to 6.8.2 * Fri Nov 23 2007 Bryan O'Sullivan - 6.8.1-2 From c2da1038f3996971e54354596890bb60490673ae Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Nov 2012 20:38:54 +0900 Subject: [PATCH 341/530] install ghc-doc-index in bindir --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 50454c4..686b869 100644 --- a/ghc.spec +++ b/ghc.spec @@ -311,6 +311,7 @@ done mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly install -p --mode=755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p %{buildroot}%{_localstatedir}/lib/ghc +install -p -m 0644 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index %endif %check @@ -368,7 +369,6 @@ fi %doc ANNOUNCE HACKING LICENSE README %{_bindir}/ghc %{_bindir}/ghc-%{version} -%{_bindir}/ghc-doc-index %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} %{_bindir}/ghci @@ -399,6 +399,7 @@ fi %dir %{_docdir}/ghc %dir %{ghcdocbasedir} %if %{undefined without_haddock} +%{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} %{ghclibdir}/haddock From 9cab3ce294a29241c294c8b4443b4b0906598f3d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Nov 2012 21:27:53 +0900 Subject: [PATCH 342/530] turn off bootstrapping for proper bootstrapped build --- ghc.spec | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index 686b869..76fd1c4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_testsuite 1 -%global without_haddock 1 +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_testsuite 1 +#%%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -29,7 +29,7 @@ Version: 7.4.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 7%{?dist} +Release: 8%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -434,9 +434,12 @@ fi %files libraries %changelog +* Sat Nov 17 2012 Jens Petersen - 7.4.2-8 +- production 7.4.2 build + http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html + * Sat Nov 17 2012 Jens Petersen - 7.4.2-7 - 7.4.2 bootstrap - http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html - update base and unix library versions - ARM StgCRun patches not longer needed - use Karel Gardas' ARM hardfloat patch committed upstream From 71c562fdd5d6de8c9aaf2fecc1521f771766fb6b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 21 Nov 2012 16:55:59 +0900 Subject: [PATCH 343/530] fix permissions of ghc-doc-index and only run when root cronjob no longer checks /etc/sysconfig/ghc-doc-index --- ghc-doc-index | 5 +++++ ghc-doc-index.cron | 12 ++++-------- ghc.spec | 10 +++++++--- 3 files changed, 16 insertions(+), 11 deletions(-) mode change 100644 => 100755 ghc-doc-index diff --git a/ghc-doc-index b/ghc-doc-index old mode 100644 new mode 100755 index eca75f1..6105d7e --- a/ghc-doc-index +++ b/ghc-doc-index @@ -10,6 +10,11 @@ if [ -f $LOCKFILE ]; then exit 0 fi +if [ "$(id -u)" != "0" ]; then + echo Need to be root! + exit 1 +fi + trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT touch $LOCKFILE diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron index e353689..4efe2ff 100755 --- a/ghc-doc-index.cron +++ b/ghc-doc-index.cron @@ -1,13 +1,9 @@ #! /bin/bash +# updates the library documentation index after updates -if [ -e /etc/sysconfig/ghc-doc-index ]; then - . /etc/sysconfig/ghc-doc-index -fi +# This can be disabled by uninstalling ghc-doc-index +# or adding ghc-doc-index to "./jobs-deny". -if [ "$CRON" = "no" ]; then - exit 0 -fi - -/usr/bin/ghc-doc-index >/dev/null +/usr/bin/ghc-doc-index exit 0 diff --git a/ghc.spec b/ghc.spec index 76fd1c4..0e85aa6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.4.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 8%{?dist} +Release: 9%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -309,9 +309,9 @@ done %if %{undefined without_haddock} mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly -install -p --mode=755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index +install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p %{buildroot}%{_localstatedir}/lib/ghc -install -p -m 0644 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index +install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index %endif %check @@ -434,6 +434,10 @@ fi %files libraries %changelog +* Wed Nov 21 2012 Jens Petersen - 7.4.2-9 +- fix permissions of ghc-doc-index and only run when root +- ghc-doc-index cronjob no longer looks at /etc/sysconfig/ghc-doc-index + * Sat Nov 17 2012 Jens Petersen - 7.4.2-8 - production 7.4.2 build http://www.haskell.org/ghc/docs/7.4.2/html/users_guide/release-7-4-2.html From 71f3050a3b6ff14a640509db7c227962307638b2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 18 Jan 2013 18:53:01 +0900 Subject: [PATCH 344/530] rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 0e85aa6..1782beb 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.4.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 9%{?dist} +Release: 10%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -434,6 +434,9 @@ fi %files libraries %changelog +* Thu Jan 17 2013 Jens Petersen - 7.4.2-10 +- rebuild for F19 libffi soname bump + * Wed Nov 21 2012 Jens Petersen - 7.4.2-9 - fix permissions of ghc-doc-index and only run when root - ghc-doc-index cronjob no longer looks at /etc/sysconfig/ghc-doc-index From ec42ddfe2568f480507d96984ffaac16fc71824f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 5 Feb 2013 13:04:03 +0900 Subject: [PATCH 345/530] move ghclibdir ownership from compiler to base lib for runtime (#907671) --- ghc.spec | 11 +++++++++-- 1 file changed, 9 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 1782beb..988509c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.4.2 # - release can only be reset if all library versions get bumped simultaneously # (eg for a major release) # - minor release numbers should be incremented monotonically -Release: 10%{?dist} +Release: 11%{?dist} Summary: Glasgow Haskell Compiler # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -271,6 +271,9 @@ ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files done +# ghc-base should own ghclibdir +echo "%dir %{ghclibdir}" >> ghc-base%{?ghc_without_shared:-devel}.files + %ghc_gen_filelists bin-package-db 0.0.0.0 %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghc-prim 0.2.0.0 @@ -288,6 +291,7 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist ghc-prim base %merge_filelist bin-package-db ghc +# add rts libs %if %{undefined ghc_without_shared} ls %{buildroot}%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^%{buildroot}||g" ghc-base.files @@ -380,7 +384,6 @@ fi %{_bindir}/runghc %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc -%dir %{ghclibdir} %{ghclibdir}/ghc %{ghclibdir}/ghc-pkg %ifnarch %{unregisterised_archs} @@ -434,6 +437,10 @@ fi %files libraries %changelog +* Tue Feb 5 2013 Jens Petersen - 7.4.2-11 +- ghclibdir should be owned at runtime by ghc-base instead of ghc-compiler + (thanks Michael Scherer, #907671) + * Thu Jan 17 2013 Jens Petersen - 7.4.2-10 - rebuild for F19 libffi soname bump From 46792007c994f0f37012de2a0280a63eedfc3a5e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 23 Apr 2013 18:33:35 +0900 Subject: [PATCH 346/530] update to new stable major version 7.6.3 - bootstrap build - use new ghc-rpm-macros-extra - no longer filter type-level package from haddock index --- .gitignore | 2 + Cabal-fix-dynamic-exec-for-TH.patch | 33 - ...12.1-gen_contents_index-haddock-path.patch | 12 - ...rt-for-ARM-hard-float-ABI-fixes-5914.patch | 1274 ----------------- ghc-7.4-silence-gen_contents_index.patch | 11 - ghc-gen_contents_index-haddock-path.patch | 11 + ghc-gen_contents_index-type-level.patch | 12 - ghc-powerpc-linker-mmap.patch | 34 - ghc-powerpc-pthread.patch | 18 - ghc-use-system-libffi.patch | 46 +- ghc.spec | 149 +- sources | 4 +- 12 files changed, 105 insertions(+), 1501 deletions(-) delete mode 100644 Cabal-fix-dynamic-exec-for-TH.patch delete mode 100644 ghc-6.12.1-gen_contents_index-haddock-path.patch delete mode 100644 ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch delete mode 100644 ghc-7.4-silence-gen_contents_index.patch create mode 100644 ghc-gen_contents_index-haddock-path.patch delete mode 100644 ghc-gen_contents_index-type-level.patch delete mode 100644 ghc-powerpc-linker-mmap.patch delete mode 100644 ghc-powerpc-pthread.patch diff --git a/.gitignore b/.gitignore index 6f437bb..9da11de 100644 --- a/.gitignore +++ b/.gitignore @@ -9,3 +9,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.4.1-src.tar.bz2 /ghc-7.4.2-src.tar.bz2 /ghc-7.4.2-testsuite.tar.bz2 +/ghc-7.6.3-src.tar.bz2 +/ghc-7.6.3-testsuite.tar.bz2 diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch deleted file mode 100644 index 5384ea7..0000000 --- a/Cabal-fix-dynamic-exec-for-TH.patch +++ /dev/null @@ -1,33 +0,0 @@ -diff -u ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs.orig ghc-7.2.0.20110728/libraries/Cabal/cabal/Distribution/Simple/GHC.hs ---- ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs.orig 2011-07-29 02:12:09.000000000 +0900 -+++ ghc-7.2.0.20110728/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs 2011-08-05 18:08:05.192042529 +0900 -@@ -778,7 +778,10 @@ - ++ ["-L"++libDir | libDir <- extraLibDirs exeBi] - ++ concat [["-framework", f] | f <- PD.frameworks exeBi] - ++ if dynExe -- then ["-dynamic"] -+ then ["-dynamic", -+ "-hisuf", "dyn_hi", -+ "-osuf", "dyn_o" -+ ] - else [] - ++ if profExe - then ["-prof", -@@ -787,13 +790,14 @@ - ] ++ ghcProfOptions exeBi - else [] - -- -- For building exe's for profiling that use TH we actually -+ -- For building exe's for profiling or dynamic that use TH we actually - -- have to build twice, once without profiling and the again - -- with profiling. This is because the code that TH needs to - -- run at compile time needs to be the vanilla ABI so it can - -- be loaded up and run by the compiler. -- when (withProfExe lbi && EnableExtension TemplateHaskell `elem` allExtensions exeBi) -- (runGhcProg (binArgs False (withDynExe lbi) False)) -+ when ((withProfExe lbi || withDynExe lbi) && -+ EnableExtension TemplateHaskell `elem` allExtensions exeBi) -+ (runGhcProg (binArgs False False False)) - - runGhcProg (binArgs True (withDynExe lbi) (withProfExe lbi)) - diff --git a/ghc-6.12.1-gen_contents_index-haddock-path.patch b/ghc-6.12.1-gen_contents_index-haddock-path.patch deleted file mode 100644 index d1034eb..0000000 --- a/ghc-6.12.1-gen_contents_index-haddock-path.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc-6.12.1/libraries/gen_contents_index\~ ghc-6.12.1/libraries/gen_contents_index ---- ghc-6.12.1/libraries/gen_contents_index~ 2009-12-11 04:11:33.000000000 +1000 -+++ ghc-6.12.1/libraries/gen_contents_index 2009-12-12 21:08:02.000000000 +1000 -@@ -20,7 +20,7 @@ - done - ;; - *) -- HADDOCK=../../../../../bin/haddock -+ HADDOCK=/usr/bin/haddock - # We don't want the GHC API to swamp the index - HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` - for HADDOCK_FILE in $HADDOCK_FILES diff --git a/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch b/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch deleted file mode 100644 index a9b897b..0000000 --- a/ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch +++ /dev/null @@ -1,1274 +0,0 @@ -From 83195ff5ba73779514e3d06b1457d45f849c7fc2 Mon Sep 17 00:00:00 2001 -From: Karel Gardas -Date: Wed, 25 Apr 2012 09:04:50 +0200 -Subject: [PATCH] add support for ARM hard-float ABI (fixes #5914) - -This patch enhances Platform's ArchARM to include ARM ABI value. It also -tweaks configure machinery to detect hard-float ABI and to set it wherever -needed. Finally when hard-float ABI is in use, pass appropriate compiler -option to the LLVM's llc. Fixes #5914. ---- - aclocal.m4 | 2 +- - compiler/main/DriverPipeline.hs | 16 +- - compiler/nativeGen/AsmCodeGen.lhs | 2 +- - compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs | 56 ++-- - compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs | 14 +- - compiler/nativeGen/RegAlloc/Linear/Main.hs | 14 +- - compiler/nativeGen/TargetReg.hs | 70 ++-- - compiler/utils/Platform.hs | 12 +- - config.guess | 482 ++++++++++---------- - configure.ac | 14 + - 10 files changed, 345 insertions(+), 337 deletions(-) - -diff --git a/aclocal.m4 b/aclocal.m4 -index 5652185..c196bdf 100644 ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -171,7 +171,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS], - ;; - arm) - GET_ARM_ISA() -- test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT}\"" -+ test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" - ;; - alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" -diff -u ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs ---- ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs.arm 2012-05-15 02:10:41.000000000 +0900 -+++ ghc-7.4.1.20120508/compiler/main/DriverPipeline.hs 2012-05-18 12:19:22.779955285 +0900 -@@ -1366,7 +1366,8 @@ - SysTools.FileOption "" input_fn, - SysTools.Option "-o", SysTools.FileOption "" output_fn] - ++ map SysTools.Option lc_opts -- ++ map SysTools.Option fpOpts) -+ ++ map SysTools.Option fpOpts -+ ++ map SysTools.Option abiOpts) - - return (next_phase, output_fn) - where -@@ -1378,12 +1379,19 @@ - -- while compiling GHC source code. It's probably due to fact that it - -- does not enable VFP by default. Let's do this manually here - fpOpts = case platformArch (targetPlatform dflags) of -- ArchARM ARMv7 ext -> if (elem VFPv3 ext) -+ ArchARM ARMv7 ext _ -> if (elem VFPv3 ext) - then ["-mattr=+v7,+vfp3"] - else if (elem VFPv3D16 ext) - then ["-mattr=+v7,+vfp3,+d16"] - else [] - _ -> [] -+ -- On Ubuntu/Debian with ARM hard float ABI, LLVM's llc still -+ -- compiles into soft-float ABI. We need to explicitly set abi -+ -- to hard -+ abiOpts = case platformArch (targetPlatform dflags) of -+ ArchARM ARMv7 _ HARD -> ["-float-abi=hard"] -+ ArchARM ARMv7 _ _ -> [] -+ _ -> [] - - ----------------------------------------------------------------------------- - -- LlvmMangle phase -@@ -1532,8 +1540,8 @@ - - elfSectionNote :: String - elfSectionNote = case platformArch (targetPlatform dflags) of -- ArchARM _ _ -> "%note" -- _ -> "@note" -+ ArchARM _ _ _ -> "%note" -+ _ -> "@note" - - -- The "link info" is a string representing the parameters of the - -- link. We save this information in the binary, and the next time we -diff --git a/compiler/nativeGen/AsmCodeGen.lhs b/compiler/nativeGen/AsmCodeGen.lhs -index 1ad1242..e976e58 100644 ---- a/compiler/nativeGen/AsmCodeGen.lhs -+++ b/compiler/nativeGen/AsmCodeGen.lhs -@@ -200,7 +200,7 @@ nativeCodeGen dflags h us cmms - ,ncgExpandTop = map SPARC.CodeGen.Expand.expandTop - ,ncgMakeFarBranches = id - } -- ArchARM _ _ -> -+ ArchARM _ _ _ -> - panic "nativeCodeGen: No NCG for ARM" - ArchPPC_64 -> - panic "nativeCodeGen: No NCG for PPC 64" -diff --git a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -index 6067f23..6cd3f00 100644 ---- a/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -+++ b/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -@@ -107,13 +107,13 @@ trivColorable - trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts exclusions - | let !cALLOCATABLE_REGS_INTEGER - = iUnbox (case platformArch platform of -- ArchX86 -> 3 -- ArchX86_64 -> 5 -- ArchPPC -> 16 -- ArchSPARC -> 14 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 3 -+ ArchX86_64 -> 5 -+ ArchPPC -> 16 -+ ArchSPARC -> 14 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_INTEGER - (virtualRegSqueeze RcInteger) - conflicts -@@ -127,13 +127,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcInteger conflicts excl - trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclusions - | let !cALLOCATABLE_REGS_FLOAT - = iUnbox (case platformArch platform of -- ArchX86 -> 0 -- ArchX86_64 -> 0 -- ArchPPC -> 0 -- ArchSPARC -> 22 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 0 -+ ArchX86_64 -> 0 -+ ArchPPC -> 0 -+ ArchSPARC -> 22 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_FLOAT - (virtualRegSqueeze RcFloat) - conflicts -@@ -147,13 +147,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcFloat conflicts exclus - trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclusions - | let !cALLOCATABLE_REGS_DOUBLE - = iUnbox (case platformArch platform of -- ArchX86 -> 6 -- ArchX86_64 -> 0 -- ArchPPC -> 26 -- ArchSPARC -> 11 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 6 -+ ArchX86_64 -> 0 -+ ArchPPC -> 26 -+ ArchSPARC -> 11 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_DOUBLE - (virtualRegSqueeze RcDouble) - conflicts -@@ -167,13 +167,13 @@ trivColorable platform virtualRegSqueeze realRegSqueeze RcDouble conflicts exclu - trivColorable platform virtualRegSqueeze realRegSqueeze RcDoubleSSE conflicts exclusions - | let !cALLOCATABLE_REGS_SSE - = iUnbox (case platformArch platform of -- ArchX86 -> 8 -- ArchX86_64 -> 10 -- ArchPPC -> 0 -- ArchSPARC -> 0 -- ArchPPC_64 -> panic "trivColorable ArchPPC_64" -- ArchARM _ _ -> panic "trivColorable ArchARM" -- ArchUnknown -> panic "trivColorable ArchUnknown") -+ ArchX86 -> 8 -+ ArchX86_64 -> 10 -+ ArchPPC -> 0 -+ ArchSPARC -> 0 -+ ArchPPC_64 -> panic "trivColorable ArchPPC_64" -+ ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchUnknown -> panic "trivColorable ArchUnknown") - , count2 <- accSqueeze (_ILIT(0)) cALLOCATABLE_REGS_SSE - (virtualRegSqueeze RcDoubleSSE) - conflicts -diff --git a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -index 6fbbd04..fd1fd27 100644 ---- a/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -+++ b/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -@@ -68,11 +68,11 @@ instance FR SPARC.FreeRegs where - maxSpillSlots :: Platform -> Int - maxSpillSlots platform - = case platformArch platform of -- ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit -- ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit -- ArchPPC -> PPC.Instr.maxSpillSlots -- ArchSPARC -> SPARC.Instr.maxSpillSlots -- ArchARM _ _ -> panic "maxSpillSlots ArchARM" -- ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" -- ArchUnknown -> panic "maxSpillSlots ArchUnknown" -+ ArchX86 -> X86.Instr.maxSpillSlots True -- 32bit -+ ArchX86_64 -> X86.Instr.maxSpillSlots False -- not 32bit -+ ArchPPC -> PPC.Instr.maxSpillSlots -+ ArchSPARC -> SPARC.Instr.maxSpillSlots -+ ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" -+ ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" -+ ArchUnknown -> panic "maxSpillSlots ArchUnknown" - -diff --git a/compiler/nativeGen/RegAlloc/Linear/Main.hs b/compiler/nativeGen/RegAlloc/Linear/Main.hs -index fc0bde4..64b0f68 100644 ---- a/compiler/nativeGen/RegAlloc/Linear/Main.hs -+++ b/compiler/nativeGen/RegAlloc/Linear/Main.hs -@@ -180,13 +180,13 @@ linearRegAlloc - linearRegAlloc dflags first_id block_live sccs - = let platform = targetPlatform dflags - in case platformArch platform of -- ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -- ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -- ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs -- ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs -- ArchARM _ _ -> panic "linearRegAlloc ArchARM" -- ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" -- ArchUnknown -> panic "linearRegAlloc ArchUnknown" -+ ArchX86 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -+ ArchX86_64 -> linearRegAlloc' platform (frInitFreeRegs :: X86.FreeRegs) first_id block_live sccs -+ ArchSPARC -> linearRegAlloc' platform (frInitFreeRegs :: SPARC.FreeRegs) first_id block_live sccs -+ ArchPPC -> linearRegAlloc' platform (frInitFreeRegs :: PPC.FreeRegs) first_id block_live sccs -+ ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" -+ ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" -+ ArchUnknown -> panic "linearRegAlloc ArchUnknown" - - linearRegAlloc' - :: (FR freeRegs, PlatformOutputable instr, Instruction instr) -diff --git a/compiler/nativeGen/TargetReg.hs b/compiler/nativeGen/TargetReg.hs -index cbc4c17..13293de 100644 ---- a/compiler/nativeGen/TargetReg.hs -+++ b/compiler/nativeGen/TargetReg.hs -@@ -50,35 +50,35 @@ import qualified SPARC.Regs as SPARC - targetVirtualRegSqueeze :: Platform -> RegClass -> VirtualReg -> FastInt - targetVirtualRegSqueeze platform - = case platformArch platform of -- ArchX86 -> X86.virtualRegSqueeze -- ArchX86_64 -> X86.virtualRegSqueeze -- ArchPPC -> PPC.virtualRegSqueeze -- ArchSPARC -> SPARC.virtualRegSqueeze -- ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" -- ArchARM _ _ -> panic "targetVirtualRegSqueeze ArchARM" -- ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" -+ ArchX86 -> X86.virtualRegSqueeze -+ ArchX86_64 -> X86.virtualRegSqueeze -+ ArchPPC -> PPC.virtualRegSqueeze -+ ArchSPARC -> SPARC.virtualRegSqueeze -+ ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" -+ ArchUnknown -> panic "targetVirtualRegSqueeze ArchUnknown" - - targetRealRegSqueeze :: Platform -> RegClass -> RealReg -> FastInt - targetRealRegSqueeze platform - = case platformArch platform of -- ArchX86 -> X86.realRegSqueeze -- ArchX86_64 -> X86.realRegSqueeze -- ArchPPC -> PPC.realRegSqueeze -- ArchSPARC -> SPARC.realRegSqueeze -- ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" -- ArchARM _ _ -> panic "targetRealRegSqueeze ArchARM" -- ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" -+ ArchX86 -> X86.realRegSqueeze -+ ArchX86_64 -> X86.realRegSqueeze -+ ArchPPC -> PPC.realRegSqueeze -+ ArchSPARC -> SPARC.realRegSqueeze -+ ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" -+ ArchUnknown -> panic "targetRealRegSqueeze ArchUnknown" - - targetClassOfRealReg :: Platform -> RealReg -> RegClass - targetClassOfRealReg platform - = case platformArch platform of -- ArchX86 -> X86.classOfRealReg -- ArchX86_64 -> X86.classOfRealReg -- ArchPPC -> PPC.classOfRealReg -- ArchSPARC -> SPARC.classOfRealReg -- ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" -- ArchARM _ _ -> panic "targetClassOfRealReg ArchARM" -- ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" -+ ArchX86 -> X86.classOfRealReg -+ ArchX86_64 -> X86.classOfRealReg -+ ArchPPC -> PPC.classOfRealReg -+ ArchSPARC -> SPARC.classOfRealReg -+ ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" -+ ArchUnknown -> panic "targetClassOfRealReg ArchUnknown" - - -- TODO: This should look at targetPlatform too - targetWordSize :: Size -@@ -87,24 +87,24 @@ targetWordSize = intSize wordWidth - targetMkVirtualReg :: Platform -> Unique -> Size -> VirtualReg - targetMkVirtualReg platform - = case platformArch platform of -- ArchX86 -> X86.mkVirtualReg -- ArchX86_64 -> X86.mkVirtualReg -- ArchPPC -> PPC.mkVirtualReg -- ArchSPARC -> SPARC.mkVirtualReg -- ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" -- ArchARM _ _ -> panic "targetMkVirtualReg ArchARM" -- ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" -+ ArchX86 -> X86.mkVirtualReg -+ ArchX86_64 -> X86.mkVirtualReg -+ ArchPPC -> PPC.mkVirtualReg -+ ArchSPARC -> SPARC.mkVirtualReg -+ ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" -+ ArchUnknown -> panic "targetMkVirtualReg ArchUnknown" - - targetRegDotColor :: Platform -> RealReg -> SDoc - targetRegDotColor platform - = case platformArch platform of -- ArchX86 -> X86.regDotColor platform -- ArchX86_64 -> X86.regDotColor platform -- ArchPPC -> PPC.regDotColor -- ArchSPARC -> SPARC.regDotColor -- ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" -- ArchARM _ _ -> panic "targetRegDotColor ArchARM" -- ArchUnknown -> panic "targetRegDotColor ArchUnknown" -+ ArchX86 -> X86.regDotColor platform -+ ArchX86_64 -> X86.regDotColor platform -+ ArchPPC -> PPC.regDotColor -+ ArchSPARC -> SPARC.regDotColor -+ ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" -+ ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" -+ ArchUnknown -> panic "targetRegDotColor ArchUnknown" - - - targetClassOfReg :: Platform -> Reg -> RegClass -diff --git a/compiler/utils/Platform.hs b/compiler/utils/Platform.hs -index 47dd779..8252621 100644 ---- a/compiler/utils/Platform.hs -+++ b/compiler/utils/Platform.hs -@@ -7,6 +7,7 @@ module Platform ( - OS(..), - ArmISA(..), - ArmISAExt(..), -+ ArmABI(..), - - target32Bit, - osElfTarget -@@ -41,7 +42,9 @@ data Arch - | ArchSPARC - | ArchARM - { armISA :: ArmISA -- , armISAExt :: [ArmISAExt] } -+ , armISAExt :: [ArmISAExt] -+ , armABI :: ArmABI -+ } - deriving (Read, Show, Eq) - - -@@ -61,7 +64,7 @@ data OS - | OSHaiku - deriving (Read, Show, Eq) - ---- | ARM Instruction Set Architecture and Extensions -+-- | ARM Instruction Set Architecture, Extensions and ABI - -- - data ArmISA - = ARMv5 -@@ -77,6 +80,11 @@ data ArmISAExt - | IWMMX2 - deriving (Read, Show, Eq) - -+data ArmABI -+ = SOFT -+ | SOFTFP -+ | HARD -+ deriving (Read, Show, Eq) - - target32Bit :: Platform -> Bool - target32Bit p = platformWordSize p == 4 -diff --git a/config.guess b/config.guess -index 463a03a..d622a44 100644 ---- a/config.guess -+++ b/config.guess -@@ -1,10 +1,10 @@ - #! /bin/sh - # Attempt to guess a canonical system name. - # Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, --# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008 --# Free Software Foundation, Inc. -+# 2000, 2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, -+# 2011, 2012 Free Software Foundation, Inc. - --timestamp='2008-11-15' -+timestamp='2012-02-10' - - # This file is free software; you can redistribute it and/or modify it - # under the terms of the GNU General Public License as published by -@@ -17,9 +17,7 @@ timestamp='2008-11-15' - # General Public License for more details. - # - # You should have received a copy of the GNU General Public License --# along with this program; if not, write to the Free Software --# Foundation, Inc., 51 Franklin Street - Fifth Floor, Boston, MA --# 02110-1301, USA. -+# along with this program; if not, see . - # - # As a special exception to the GNU General Public License, if you - # distribute this file as part of a program that contains a -@@ -27,16 +25,16 @@ timestamp='2008-11-15' - # the same distribution terms that you use for the rest of that program. - - --# Originally written by Per Bothner . --# Please send patches to . Submit a context --# diff and a properly formatted ChangeLog entry. -+# Originally written by Per Bothner. Please send patches (context -+# diff format) to and include a ChangeLog -+# entry. - # - # This script attempts to guess a canonical system name similar to - # config.sub. If it succeeds, it prints the system name on stdout, and - # exits with 0. Otherwise, it exits with 1. - # --# The plan is that this can be called by configure scripts if you --# don't specify an explicit build system type. -+# You can get the latest version of this script from: -+# http://git.savannah.gnu.org/gitweb/?p=config.git;a=blob_plain;f=config.guess;hb=HEAD - - me=`echo "$0" | sed -e 's,.*/,,'` - -@@ -56,8 +54,9 @@ version="\ - GNU config.guess ($timestamp) - - Originally written by Per Bothner. --Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, 2001, --2002, 2003, 2004, 2005, 2006, 2007, 2008 Free Software Foundation, Inc. -+Copyright (C) 1992, 1993, 1994, 1995, 1996, 1997, 1998, 1999, 2000, -+2001, 2002, 2003, 2004, 2005, 2006, 2007, 2008, 2009, 2010, 2011, 2012 -+Free Software Foundation, Inc. - - This is free software; see the source for copying conditions. There is NO - warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE." -@@ -144,7 +143,7 @@ UNAME_VERSION=`(uname -v) 2>/dev/null` || UNAME_VERSION=unknown - case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - *:NetBSD:*:*) - # NetBSD (nbsd) targets should (where applicable) match one or -- # more of the tupples: *-*-netbsdelf*, *-*-netbsdaout*, -+ # more of the tuples: *-*-netbsdelf*, *-*-netbsdaout*, - # *-*-netbsdecoff* and *-*-netbsd*. For targets that recently - # switched to ELF, *-*-netbsd* would select the old - # object file format. This provides both forward -@@ -170,7 +169,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - arm*|i386|m68k|ns32k|sh3*|sparc|vax) - eval $set_cc_for_build - if echo __ELF__ | $CC_FOR_BUILD -E - 2>/dev/null \ -- | grep __ELF__ >/dev/null -+ | grep -q __ELF__ - then - # Once all utilities can be ECOFF (netbsdecoff) or a.out (netbsdaout). - # Return netbsd for either. FIX? -@@ -180,7 +179,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - fi - ;; - *) -- os=netbsd -+ os=netbsd - ;; - esac - # The OS release -@@ -223,7 +222,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $3}'` - ;; - *5.*) -- UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` -+ UNAME_RELEASE=`/usr/sbin/sizer -v | awk '{print $4}'` - ;; - esac - # According to Compaq, /usr/sbin/psrinfo has been available on -@@ -269,7 +268,10 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # A Xn.n version is an unreleased experimental baselevel. - # 1.2 uses "1.2" for uname -r. - echo ${UNAME_MACHINE}-dec-osf`echo ${UNAME_RELEASE} | sed -e 's/^[PVTX]//' | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` -- exit ;; -+ # Reset EXIT trap before exiting to avoid spurious non-zero exit code. -+ exitcode=$? -+ trap '' 0 -+ exit $exitcode ;; - Alpha\ *:Windows_NT*:*) - # How do we know it's Interix rather than the generic POSIX subsystem? - # Should we change UNAME_MACHINE based on the output of uname instead -@@ -295,7 +297,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - echo s390-ibm-zvmoe - exit ;; - *:OS400:*:*) -- echo powerpc-ibm-os400 -+ echo powerpc-ibm-os400 - exit ;; - arm:RISC*:1.[012]*:*|arm:riscix:1.[012]*:*) - echo arm-acorn-riscix${UNAME_RELEASE} -@@ -324,12 +326,18 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - case `/usr/bin/uname -p` in - sparc) echo sparc-icl-nx7; exit ;; - esac ;; -+ s390x:SunOS:*:*) -+ echo ${UNAME_MACHINE}-ibm-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` -+ exit ;; - sun4H:SunOS:5.*:*) - echo sparc-hal-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` - exit ;; - sun4*:SunOS:5.*:* | tadpole*:SunOS:5.*:*) - echo sparc-sun-solaris2`echo ${UNAME_RELEASE}|sed -e 's/[^.]*//'` - exit ;; -+ i86pc:AuroraUX:5.*:* | i86xen:AuroraUX:5.*:*) -+ echo i386-pc-auroraux${UNAME_RELEASE} -+ exit ;; - i86pc:SunOS:5.*:* | i86xen:SunOS:5.*:*) - eval $set_cc_for_build - SUN_ARCH="i386" -@@ -337,17 +345,7 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # Note that the Sun cc does not turn __LP64__ into 1 like gcc does. - # This test works for both compilers. - if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then -- # bash is not able to generate correct code here -- # i.e. it leaves \ns there -- # so we need to use /usr/bin/echo to get what we want -- # note that if config.guess is run by /bin/sh then -- # this works as expected even without /usr/bin/echo -- # but the problem is that configure is clever enough -- # to find bash installed and then runs config.guess -- # by bash instead of by /bin/sh -- # It seems that using /usr/bin/echo here is the most -- # portable Solaris fix -- if /usr/bin/echo '\n#ifdef __amd64\nIS_64BIT_ARCH\n#endif' | \ -+ if (echo '#ifdef __amd64'; echo IS_64BIT_ARCH; echo '#endif') | \ - (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ - grep IS_64BIT_ARCH >/dev/null - then -@@ -398,23 +396,23 @@ case "${UNAME_MACHINE}:${UNAME_SYSTEM}:${UNAME_RELEASE}:${UNAME_VERSION}" in - # MiNT. But MiNT is downward compatible to TOS, so this should - # be no problem. - atarist[e]:*MiNT:*:* | atarist[e]:*mint:*:* | atarist[e]:*TOS:*:*) -- echo m68k-atari-mint${UNAME_RELEASE} -+ echo m68k-atari-mint${UNAME_RELEASE} - exit ;; - atari*:*MiNT:*:* | atari*:*mint:*:* | atarist[e]:*TOS:*:*) - echo m68k-atari-mint${UNAME_RELEASE} -- exit ;; -+ exit ;; - *falcon*:*MiNT:*:* | *falcon*:*mint:*:* | *falcon*:*TOS:*:*) -- echo m68k-atari-mint${UNAME_RELEASE} -+ echo m68k-atari-mint${UNAME_RELEASE} - exit ;; - milan*:*MiNT:*:* | milan*:*mint:*:* | *milan*:*TOS:*:*) -- echo m68k-milan-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-milan-mint${UNAME_RELEASE} -+ exit ;; - hades*:*MiNT:*:* | hades*:*mint:*:* | *hades*:*TOS:*:*) -- echo m68k-hades-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-hades-mint${UNAME_RELEASE} -+ exit ;; - *:*MiNT:*:* | *:*mint:*:* | *:*TOS:*:*) -- echo m68k-unknown-mint${UNAME_RELEASE} -- exit ;; -+ echo m68k-unknown-mint${UNAME_RELEASE} -+ exit ;; - m68k:machten:*:*) - echo m68k-apple-machten${UNAME_RELEASE} - exit ;; -@@ -484,8 +482,8 @@ EOF - echo m88k-motorola-sysv3 - exit ;; - AViiON:dgux:*:*) -- # DG/UX returns AViiON for all architectures -- UNAME_PROCESSOR=`/usr/bin/uname -p` -+ # DG/UX returns AViiON for all architectures -+ UNAME_PROCESSOR=`/usr/bin/uname -p` - if [ $UNAME_PROCESSOR = mc88100 ] || [ $UNAME_PROCESSOR = mc88110 ] - then - if [ ${TARGET_BINARY_INTERFACE}x = m88kdguxelfx ] || \ -@@ -498,7 +496,7 @@ EOF - else - echo i586-dg-dgux${UNAME_RELEASE} - fi -- exit ;; -+ exit ;; - M88*:DolphinOS:*:*) # DolphinOS (SVR3) - echo m88k-dolphin-sysv3 - exit ;; -@@ -555,7 +553,7 @@ EOF - echo rs6000-ibm-aix3.2 - fi - exit ;; -- *:AIX:*:[456]) -+ *:AIX:*:[4567]) - IBM_CPU_ID=`/usr/sbin/lsdev -C -c processor -S available | sed 1q | awk '{ print $1 }'` - if /usr/sbin/lsattr -El ${IBM_CPU_ID} | grep ' POWER' >/dev/null 2>&1; then - IBM_ARCH=rs6000 -@@ -598,52 +596,52 @@ EOF - 9000/[678][0-9][0-9]) - if [ -x /usr/bin/getconf ]; then - sc_cpu_version=`/usr/bin/getconf SC_CPU_VERSION 2>/dev/null` -- sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` -- case "${sc_cpu_version}" in -- 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 -- 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 -- 532) # CPU_PA_RISC2_0 -- case "${sc_kernel_bits}" in -- 32) HP_ARCH="hppa2.0n" ;; -- 64) HP_ARCH="hppa2.0w" ;; -+ sc_kernel_bits=`/usr/bin/getconf SC_KERNEL_BITS 2>/dev/null` -+ case "${sc_cpu_version}" in -+ 523) HP_ARCH="hppa1.0" ;; # CPU_PA_RISC1_0 -+ 528) HP_ARCH="hppa1.1" ;; # CPU_PA_RISC1_1 -+ 532) # CPU_PA_RISC2_0 -+ case "${sc_kernel_bits}" in -+ 32) HP_ARCH="hppa2.0n" ;; -+ 64) HP_ARCH="hppa2.0w" ;; - '') HP_ARCH="hppa2.0" ;; # HP-UX 10.20 -- esac ;; -- esac -+ esac ;; -+ esac - fi - if [ "${HP_ARCH}" = "" ]; then - eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -+ sed 's/^ //' << EOF >$dummy.c - -- #define _HPUX_SOURCE -- #include -- #include -+ #define _HPUX_SOURCE -+ #include -+ #include - -- int main () -- { -- #if defined(_SC_KERNEL_BITS) -- long bits = sysconf(_SC_KERNEL_BITS); -- #endif -- long cpu = sysconf (_SC_CPU_VERSION); -+ int main () -+ { -+ #if defined(_SC_KERNEL_BITS) -+ long bits = sysconf(_SC_KERNEL_BITS); -+ #endif -+ long cpu = sysconf (_SC_CPU_VERSION); - -- switch (cpu) -- { -- case CPU_PA_RISC1_0: puts ("hppa1.0"); break; -- case CPU_PA_RISC1_1: puts ("hppa1.1"); break; -- case CPU_PA_RISC2_0: -- #if defined(_SC_KERNEL_BITS) -- switch (bits) -- { -- case 64: puts ("hppa2.0w"); break; -- case 32: puts ("hppa2.0n"); break; -- default: puts ("hppa2.0"); break; -- } break; -- #else /* !defined(_SC_KERNEL_BITS) */ -- puts ("hppa2.0"); break; -- #endif -- default: puts ("hppa1.0"); break; -- } -- exit (0); -- } -+ switch (cpu) -+ { -+ case CPU_PA_RISC1_0: puts ("hppa1.0"); break; -+ case CPU_PA_RISC1_1: puts ("hppa1.1"); break; -+ case CPU_PA_RISC2_0: -+ #if defined(_SC_KERNEL_BITS) -+ switch (bits) -+ { -+ case 64: puts ("hppa2.0w"); break; -+ case 32: puts ("hppa2.0n"); break; -+ default: puts ("hppa2.0"); break; -+ } break; -+ #else /* !defined(_SC_KERNEL_BITS) */ -+ puts ("hppa2.0"); break; -+ #endif -+ default: puts ("hppa1.0"); break; -+ } -+ exit (0); -+ } - EOF - (CCOPTS= $CC_FOR_BUILD -o $dummy $dummy.c 2>/dev/null) && HP_ARCH=`$dummy` - test -z "$HP_ARCH" && HP_ARCH=hppa -@@ -663,7 +661,7 @@ EOF - # => hppa64-hp-hpux11.23 - - if echo __LP64__ | (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | -- grep __LP64__ >/dev/null -+ grep -q __LP64__ - then - HP_ARCH="hppa2.0w" - else -@@ -734,22 +732,22 @@ EOF - exit ;; - C1*:ConvexOS:*:* | convex:ConvexOS:C1*:*) - echo c1-convex-bsd -- exit ;; -+ exit ;; - C2*:ConvexOS:*:* | convex:ConvexOS:C2*:*) - if getsysinfo -f scalar_acc - then echo c32-convex-bsd - else echo c2-convex-bsd - fi -- exit ;; -+ exit ;; - C34*:ConvexOS:*:* | convex:ConvexOS:C34*:*) - echo c34-convex-bsd -- exit ;; -+ exit ;; - C38*:ConvexOS:*:* | convex:ConvexOS:C38*:*) - echo c38-convex-bsd -- exit ;; -+ exit ;; - C4*:ConvexOS:*:* | convex:ConvexOS:C4*:*) - echo c4-convex-bsd -- exit ;; -+ exit ;; - CRAY*Y-MP:*:*:*) - echo ymp-cray-unicos${UNAME_RELEASE} | sed -e 's/\.[^.]*$/.X/' - exit ;; -@@ -773,14 +771,14 @@ EOF - exit ;; - F30[01]:UNIX_System_V:*:* | F700:UNIX_System_V:*:*) - FUJITSU_PROC=`uname -m | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz'` -- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -- FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` -- echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -- exit ;; -+ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -+ FUJITSU_REL=`echo ${UNAME_RELEASE} | sed -e 's/ /_/'` -+ echo "${FUJITSU_PROC}-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -+ exit ;; - 5000:UNIX_System_V:4.*:*) -- FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -- FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` -- echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" -+ FUJITSU_SYS=`uname -p | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/\///'` -+ FUJITSU_REL=`echo ${UNAME_RELEASE} | tr 'ABCDEFGHIJKLMNOPQRSTUVWXYZ' 'abcdefghijklmnopqrstuvwxyz' | sed -e 's/ /_/'` -+ echo "sparc-fujitsu-${FUJITSU_SYS}${FUJITSU_REL}" - exit ;; - i*86:BSD/386:*:* | i*86:BSD/OS:*:* | *:Ascend\ Embedded/OS:*:*) - echo ${UNAME_MACHINE}-pc-bsdi${UNAME_RELEASE} -@@ -792,13 +790,12 @@ EOF - echo ${UNAME_MACHINE}-unknown-bsdi${UNAME_RELEASE} - exit ;; - *:FreeBSD:*:*) -- case ${UNAME_MACHINE} in -- pc98) -- echo i386-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; -+ UNAME_PROCESSOR=`/usr/bin/uname -p` -+ case ${UNAME_PROCESSOR} in - amd64) - echo x86_64-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; - *) -- echo ${UNAME_MACHINE}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; -+ echo ${UNAME_PROCESSOR}-unknown-freebsd`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` ;; - esac - exit ;; - i*:CYGWIN*:*) -@@ -807,19 +804,22 @@ EOF - *:MINGW*:*) - echo ${UNAME_MACHINE}-pc-mingw32 - exit ;; -+ i*:MSYS*:*) -+ echo ${UNAME_MACHINE}-pc-msys -+ exit ;; - i*:windows32*:*) -- # uname -m includes "-pc" on this system. -- echo ${UNAME_MACHINE}-mingw32 -+ # uname -m includes "-pc" on this system. -+ echo ${UNAME_MACHINE}-mingw32 - exit ;; - i*:PW*:*) - echo ${UNAME_MACHINE}-pc-pw32 - exit ;; -- *:Interix*:[3456]*) -- case ${UNAME_MACHINE} in -+ *:Interix*:*) -+ case ${UNAME_MACHINE} in - x86) - echo i586-pc-interix${UNAME_RELEASE} - exit ;; -- EM64T | authenticamd | genuineintel) -+ authenticamd | genuineintel | EM64T) - echo x86_64-unknown-interix${UNAME_RELEASE} - exit ;; - IA64) -@@ -829,6 +829,9 @@ EOF - [345]86:Windows_95:* | [345]86:Windows_98:* | [345]86:Windows_NT:*) - echo i${UNAME_MACHINE}-pc-mks - exit ;; -+ 8664:Windows_NT:*) -+ echo x86_64-pc-mks -+ exit ;; - i*:Windows_NT*:* | Pentium*:Windows_NT*:*) - # How do we know it's Interix rather than the generic POSIX subsystem? - # It also conflicts with pre-2.0 versions of AT&T UWIN. Should we -@@ -858,6 +861,27 @@ EOF - i*86:Minix:*:*) - echo ${UNAME_MACHINE}-pc-minix - exit ;; -+ aarch64:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ aarch64_be:Linux:*:*) -+ UNAME_MACHINE=aarch64_be -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ alpha:Linux:*:*) -+ case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in -+ EV5) UNAME_MACHINE=alphaev5 ;; -+ EV56) UNAME_MACHINE=alphaev56 ;; -+ PCA56) UNAME_MACHINE=alphapca56 ;; -+ PCA57) UNAME_MACHINE=alphapca56 ;; -+ EV6) UNAME_MACHINE=alphaev6 ;; -+ EV67) UNAME_MACHINE=alphaev67 ;; -+ EV68*) UNAME_MACHINE=alphaev68 ;; -+ esac -+ objdump --private-headers /bin/sh | grep -q ld.so.1 -+ if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi -+ echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} -+ exit ;; - arm*:Linux:*:*) - eval $set_cc_for_build - if echo __ARM_EABI__ | $CC_FOR_BUILD -E - 2>/dev/null \ -@@ -865,20 +889,40 @@ EOF - then - echo ${UNAME_MACHINE}-unknown-linux-gnu - else -- echo ${UNAME_MACHINE}-unknown-linux-gnueabi -+ if echo __ARM_PCS_VFP | $CC_FOR_BUILD -E - 2>/dev/null \ -+ | grep -q __ARM_PCS_VFP -+ then -+ echo ${UNAME_MACHINE}-unknown-linux-gnueabi -+ else -+ echo ${UNAME_MACHINE}-unknown-linux-gnueabihf -+ fi - fi - exit ;; - avr32*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - cris:Linux:*:*) -- echo cris-axis-linux-gnu -+ echo ${UNAME_MACHINE}-axis-linux-gnu - exit ;; - crisv32:Linux:*:*) -- echo crisv32-axis-linux-gnu -+ echo ${UNAME_MACHINE}-axis-linux-gnu - exit ;; - frv:Linux:*:*) -- echo frv-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ hexagon:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; -+ i*86:Linux:*:*) -+ LIBC=gnu -+ eval $set_cc_for_build -+ sed 's/^ //' << EOF >$dummy.c -+ #ifdef __dietlibc__ -+ LIBC=dietlibc -+ #endif -+EOF -+ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^LIBC'` -+ echo "${UNAME_MACHINE}-pc-linux-${LIBC}" - exit ;; - ia64:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu -@@ -889,78 +933,34 @@ EOF - m68*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -- mips:Linux:*:*) -- eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -- #undef CPU -- #undef mips -- #undef mipsel -- #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) -- CPU=mipsel -- #else -- #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) -- CPU=mips -- #else -- CPU= -- #endif -- #endif --EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^CPU/{ -- s: ::g -- p -- }'`" -- test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } -- ;; -- mips64:Linux:*:*) -+ mips:Linux:*:* | mips64:Linux:*:*) - eval $set_cc_for_build - sed 's/^ //' << EOF >$dummy.c - #undef CPU -- #undef mips64 -- #undef mips64el -+ #undef ${UNAME_MACHINE} -+ #undef ${UNAME_MACHINE}el - #if defined(__MIPSEL__) || defined(__MIPSEL) || defined(_MIPSEL) || defined(MIPSEL) -- CPU=mips64el -+ CPU=${UNAME_MACHINE}el - #else - #if defined(__MIPSEB__) || defined(__MIPSEB) || defined(_MIPSEB) || defined(MIPSEB) -- CPU=mips64 -+ CPU=${UNAME_MACHINE} - #else - CPU= - #endif - #endif - EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^CPU/{ -- s: ::g -- p -- }'`" -+ eval `$CC_FOR_BUILD -E $dummy.c 2>/dev/null | grep '^CPU'` - test x"${CPU}" != x && { echo "${CPU}-unknown-linux-gnu"; exit; } - ;; - or32:Linux:*:*) -- echo or32-unknown-linux-gnu -- exit ;; -- ppc:Linux:*:*) -- echo powerpc-unknown-linux-gnu -- exit ;; -- ppc64:Linux:*:*) -- echo powerpc64-unknown-linux-gnu -- exit ;; -- alpha:Linux:*:*) -- case `sed -n '/^cpu model/s/^.*: \(.*\)/\1/p' < /proc/cpuinfo` in -- EV5) UNAME_MACHINE=alphaev5 ;; -- EV56) UNAME_MACHINE=alphaev56 ;; -- PCA56) UNAME_MACHINE=alphapca56 ;; -- PCA57) UNAME_MACHINE=alphapca56 ;; -- EV6) UNAME_MACHINE=alphaev6 ;; -- EV67) UNAME_MACHINE=alphaev67 ;; -- EV68*) UNAME_MACHINE=alphaev68 ;; -- esac -- objdump --private-headers /bin/sh | grep ld.so.1 >/dev/null -- if test "$?" = 0 ; then LIBC="libc1" ; else LIBC="" ; fi -- echo ${UNAME_MACHINE}-unknown-linux-gnu${LIBC} -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - padre:Linux:*:*) - echo sparc-unknown-linux-gnu - exit ;; -+ parisc64:Linux:*:* | hppa64:Linux:*:*) -+ echo hppa64-unknown-linux-gnu -+ exit ;; - parisc:Linux:*:* | hppa:Linux:*:*) - # Look for CPU level - case `grep '^cpu[^a-z]*:' /proc/cpuinfo 2>/dev/null | cut -d' ' -f2` in -@@ -969,14 +969,17 @@ EOF - *) echo hppa-unknown-linux-gnu ;; - esac - exit ;; -- parisc64:Linux:*:* | hppa64:Linux:*:*) -- echo hppa64-unknown-linux-gnu -+ ppc64:Linux:*:*) -+ echo powerpc64-unknown-linux-gnu -+ exit ;; -+ ppc:Linux:*:*) -+ echo powerpc-unknown-linux-gnu - exit ;; - s390:Linux:*:* | s390x:Linux:*:*) - echo ${UNAME_MACHINE}-ibm-linux - exit ;; - sh64*:Linux:*:*) -- echo ${UNAME_MACHINE}-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - sh*:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu -@@ -984,75 +987,18 @@ EOF - sparc:Linux:*:* | sparc64:Linux:*:*) - echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -+ tile*:Linux:*:*) -+ echo ${UNAME_MACHINE}-unknown-linux-gnu -+ exit ;; - vax:Linux:*:*) - echo ${UNAME_MACHINE}-dec-linux-gnu - exit ;; - x86_64:Linux:*:*) -- echo x86_64-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; - xtensa*:Linux:*:*) -- echo ${UNAME_MACHINE}-unknown-linux-gnu -+ echo ${UNAME_MACHINE}-unknown-linux-gnu - exit ;; -- i*86:Linux:*:*) -- # The BFD linker knows what the default object file format is, so -- # first see if it will tell us. cd to the root directory to prevent -- # problems with other programs or directories called `ld' in the path. -- # Set LC_ALL=C to ensure ld outputs messages in English. -- ld_supported_targets=`cd /; LC_ALL=C ld --help 2>&1 \ -- | sed -ne '/supported targets:/!d -- s/[ ][ ]*/ /g -- s/.*supported targets: *// -- s/ .*// -- p'` -- case "$ld_supported_targets" in -- elf32-i386) -- TENTATIVE="${UNAME_MACHINE}-pc-linux-gnu" -- ;; -- a.out-i386-linux) -- echo "${UNAME_MACHINE}-pc-linux-gnuaout" -- exit ;; -- "") -- # Either a pre-BFD a.out linker (linux-gnuoldld) or -- # one that does not give us useful --help. -- echo "${UNAME_MACHINE}-pc-linux-gnuoldld" -- exit ;; -- esac -- # Determine whether the default compiler is a.out or elf -- eval $set_cc_for_build -- sed 's/^ //' << EOF >$dummy.c -- #include -- #ifdef __ELF__ -- # ifdef __GLIBC__ -- # if __GLIBC__ >= 2 -- LIBC=gnu -- # else -- LIBC=gnulibc1 -- # endif -- # else -- LIBC=gnulibc1 -- # endif -- #else -- #if defined(__INTEL_COMPILER) || defined(__PGI) || defined(__SUNPRO_C) || defined(__SUNPRO_CC) -- LIBC=gnu -- #else -- LIBC=gnuaout -- #endif -- #endif -- #ifdef __dietlibc__ -- LIBC=dietlibc -- #endif --EOF -- eval "`$CC_FOR_BUILD -E $dummy.c 2>/dev/null | sed -n ' -- /^LIBC/{ -- s: ::g -- p -- }'`" -- test x"${LIBC}" != x && { -- echo "${UNAME_MACHINE}-pc-linux-${LIBC}" -- exit -- } -- test x"${TENTATIVE}" != x && { echo "${TENTATIVE}"; exit; } -- ;; - i*86:DYNIX/ptx:4*:*) - # ptx 4.0 does uname -s correctly, with DYNIX/ptx in there. - # earlier versions are messed up and put the nodename in both -@@ -1060,11 +1006,11 @@ EOF - echo i386-sequent-sysv4 - exit ;; - i*86:UNIX_SV:4.2MP:2.*) -- # Unixware is an offshoot of SVR4, but it has its own version -- # number series starting with 2... -- # I am not positive that other SVR4 systems won't match this, -+ # Unixware is an offshoot of SVR4, but it has its own version -+ # number series starting with 2... -+ # I am not positive that other SVR4 systems won't match this, - # I just have to hope. -- rms. -- # Use sysv4.2uw... so that sysv4* matches it. -+ # Use sysv4.2uw... so that sysv4* matches it. - echo ${UNAME_MACHINE}-pc-sysv4.2uw${UNAME_VERSION} - exit ;; - i*86:OS/2:*:*) -@@ -1081,7 +1027,7 @@ EOF - i*86:syllable:*:*) - echo ${UNAME_MACHINE}-pc-syllable - exit ;; -- i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.0*:*) -+ i*86:LynxOS:2.*:* | i*86:LynxOS:3.[01]*:* | i*86:LynxOS:4.[02]*:*) - echo i386-unknown-lynxos${UNAME_RELEASE} - exit ;; - i*86:*DOS:*:*) -@@ -1096,7 +1042,7 @@ EOF - fi - exit ;; - i*86:*:5:[678]*) -- # UnixWare 7.x, OpenUNIX and OpenServer 6. -+ # UnixWare 7.x, OpenUNIX and OpenServer 6. - case `/bin/uname -X | grep "^Machine"` in - *486*) UNAME_MACHINE=i486 ;; - *Pentium) UNAME_MACHINE=i586 ;; -@@ -1124,10 +1070,13 @@ EOF - exit ;; - pc:*:*:*) - # Left here for compatibility: -- # uname -m prints for DJGPP always 'pc', but it prints nothing about -- # the processor, so we play safe by assuming i386. -- echo i386-pc-msdosdjgpp -- exit ;; -+ # uname -m prints for DJGPP always 'pc', but it prints nothing about -+ # the processor, so we play safe by assuming i586. -+ # Note: whatever this is, it MUST be the same as what config.sub -+ # prints for the "djgpp" host, or else GDB configury will decide that -+ # this is a cross-build. -+ echo i586-pc-msdosdjgpp -+ exit ;; - Intel:Mach:3*:*) - echo i386-pc-mach3 - exit ;; -@@ -1162,8 +1111,18 @@ EOF - /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ - && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; - 3[34]??:*:4.0:* | 3[34]??,*:*:4.0:*) -- /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -- && { echo i486-ncr-sysv4; exit; } ;; -+ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -+ && { echo i486-ncr-sysv4; exit; } ;; -+ NCR*:*:4.2:* | MPRAS*:*:4.2:*) -+ OS_REL='.3' -+ test -r /etc/.relid \ -+ && OS_REL=.`sed -n 's/[^ ]* [^ ]* \([0-9][0-9]\).*/\1/p' < /etc/.relid` -+ /bin/uname -p 2>/dev/null | grep 86 >/dev/null \ -+ && { echo i486-ncr-sysv4.3${OS_REL}; exit; } -+ /bin/uname -p 2>/dev/null | /bin/grep entium >/dev/null \ -+ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } -+ /bin/uname -p 2>/dev/null | /bin/grep pteron >/dev/null \ -+ && { echo i586-ncr-sysv4.3${OS_REL}; exit; } ;; - m68*:LynxOS:2.*:* | m68*:LynxOS:3.0*:*) - echo m68k-unknown-lynxos${UNAME_RELEASE} - exit ;; -@@ -1176,7 +1135,7 @@ EOF - rs6000:LynxOS:2.*:*) - echo rs6000-unknown-lynxos${UNAME_RELEASE} - exit ;; -- PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.0*:*) -+ PowerPC:LynxOS:2.*:* | PowerPC:LynxOS:3.[01]*:* | PowerPC:LynxOS:4.[02]*:*) - echo powerpc-unknown-lynxos${UNAME_RELEASE} - exit ;; - SM[BE]S:UNIX_SV:*:*) -@@ -1196,10 +1155,10 @@ EOF - echo ns32k-sni-sysv - fi - exit ;; -- PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort -- # says -- echo i586-unisys-sysv4 -- exit ;; -+ PENTIUM:*:4.0*:*) # Unisys `ClearPath HMP IX 4000' SVR4/MP effort -+ # says -+ echo i586-unisys-sysv4 -+ exit ;; - *:UNIX_System_V:4*:FTX*) - # From Gerald Hewes . - # How about differentiating between stratus architectures? -djm -@@ -1225,11 +1184,11 @@ EOF - exit ;; - R[34]000:*System_V*:*:* | R4000:UNIX_SYSV:*:* | R*000:UNIX_SV:*:*) - if [ -d /usr/nec ]; then -- echo mips-nec-sysv${UNAME_RELEASE} -+ echo mips-nec-sysv${UNAME_RELEASE} - else -- echo mips-unknown-sysv${UNAME_RELEASE} -+ echo mips-unknown-sysv${UNAME_RELEASE} - fi -- exit ;; -+ exit ;; - BeBox:BeOS:*:*) # BeOS running on hardware made by Be, PPC only. - echo powerpc-be-beos - exit ;; -@@ -1269,6 +1228,16 @@ EOF - *:Darwin:*:*) - UNAME_PROCESSOR=`uname -p` || UNAME_PROCESSOR=unknown - case $UNAME_PROCESSOR in -+ i386) -+ eval $set_cc_for_build -+ if [ "$CC_FOR_BUILD" != 'no_compiler_found' ]; then -+ if (echo '#ifdef __LP64__'; echo IS_64BIT_ARCH; echo '#endif') | \ -+ (CCOPTS= $CC_FOR_BUILD -E - 2>/dev/null) | \ -+ grep IS_64BIT_ARCH >/dev/null -+ then -+ UNAME_PROCESSOR="x86_64" -+ fi -+ fi ;; - unknown) UNAME_PROCESSOR=powerpc ;; - esac - echo ${UNAME_PROCESSOR}-apple-darwin${UNAME_RELEASE} -@@ -1284,6 +1253,9 @@ EOF - *:QNX:*:4*) - echo i386-pc-qnx - exit ;; -+ NEO-?:NONSTOP_KERNEL:*:*) -+ echo neo-tandem-nsk${UNAME_RELEASE} -+ exit ;; - NSE-?:NONSTOP_KERNEL:*:*) - echo nse-tandem-nsk${UNAME_RELEASE} - exit ;; -@@ -1329,13 +1301,13 @@ EOF - echo pdp10-unknown-its - exit ;; - SEI:*:*:SEIUX) -- echo mips-sei-seiux${UNAME_RELEASE} -+ echo mips-sei-seiux${UNAME_RELEASE} - exit ;; - *:DragonFly:*:*) - echo ${UNAME_MACHINE}-unknown-dragonfly`echo ${UNAME_RELEASE}|sed -e 's/[-(].*//'` - exit ;; - *:*VMS:*:*) -- UNAME_MACHINE=`(uname -p) 2>/dev/null` -+ UNAME_MACHINE=`(uname -p) 2>/dev/null` - case "${UNAME_MACHINE}" in - A*) echo alpha-dec-vms ; exit ;; - I*) echo ia64-dec-vms ; exit ;; -@@ -1350,6 +1322,12 @@ EOF - i*86:rdos:*:*) - echo ${UNAME_MACHINE}-pc-rdos - exit ;; -+ i*86:AROS:*:*) -+ echo ${UNAME_MACHINE}-pc-aros -+ exit ;; -+ x86_64:VMkernel:*:*) -+ echo ${UNAME_MACHINE}-unknown-esx -+ exit ;; - esac - - #echo '(No uname command or uname output not recognized.)' 1>&2 -@@ -1372,11 +1350,11 @@ main () - #include - printf ("m68k-sony-newsos%s\n", - #ifdef NEWSOS4 -- "4" -+ "4" - #else -- "" -+ "" - #endif -- ); exit (0); -+ ); exit (0); - #endif - #endif - -diff --git a/configure.ac b/configure.ac -index 9237c77..8e3d9d2 100644 ---- a/configure.ac -+++ b/configure.ac -@@ -210,6 +210,20 @@ AC_CANONICAL_BUILD - AC_CANONICAL_HOST - AC_CANONICAL_TARGET - -+# Testing ARM ABI -+# required for code generation (LLVM options) -+ARM_ABI=SOFT -+echo HOST: $host -+ -+case $host in -+ arm*-*-linux-gnueabihf) -+ ARM_ABI=HARD -+ ;; -+ arm*-*-linux-gnueabi) -+ ARM_ABI=SOFTFP -+ ;; -+esac -+ - FPTOOLS_SET_PLATFORM_VARS - - # Verify that the installed (bootstrap) GHC is capable of generating --- -1.7.4.3 - diff --git a/ghc-7.4-silence-gen_contents_index.patch b/ghc-7.4-silence-gen_contents_index.patch deleted file mode 100644 index d000b8b..0000000 --- a/ghc-7.4-silence-gen_contents_index.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-7.4.1/libraries/gen_contents_index~ 2012-09-30 16:14:39.368295240 +0900 -+++ ghc-7.4.1/libraries/gen_contents_index 2012-10-30 19:12:10.017398594 +0900 -@@ -50,7 +50,7 @@ - esac - - # Now create the combined contents and index pages --echo $HADDOCK_ARGS -+#echo $HADDOCK_ARGS - $HADDOCK --gen-index --gen-contents -o . \ - -t "Haskell Hierarchical Libraries" \ - -p "prologue.txt" \ diff --git a/ghc-gen_contents_index-haddock-path.patch b/ghc-gen_contents_index-haddock-path.patch new file mode 100644 index 0000000..64ede18 --- /dev/null +++ b/ghc-gen_contents_index-haddock-path.patch @@ -0,0 +1,11 @@ +--- ghc-7.6.3/libraries/gen_contents_index~ 2013-04-19 06:22:46.000000000 +0900 ++++ ghc-7.6.3/libraries/gen_contents_index 2013-04-22 12:07:48.922152864 +0900 +@@ -60,7 +60,7 @@ + done + done + else +- HADDOCK=../../../../../bin/haddock ++ HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index + HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` + HADDOCK_ARGS="-p prologue.txt" diff --git a/ghc-gen_contents_index-type-level.patch b/ghc-gen_contents_index-type-level.patch deleted file mode 100644 index 05a9e42..0000000 --- a/ghc-gen_contents_index-type-level.patch +++ /dev/null @@ -1,12 +0,0 @@ -diff -u ghc-6.12.3/libraries/gen_contents_index\~ ghc-6.12.3/libraries/gen_contents_index ---- ghc-6.12.3/libraries/gen_contents_index~ 2010-09-14 13:03:12.000000000 +1000 -+++ ghc-6.12.3/libraries/gen_contents_index 2010-11-04 16:41:32.000000000 +1000 -@@ -24,7 +24,7 @@ - *) - HADDOCK=/usr/bin/haddock - # We don't want the GHC API to swamp the index -- HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` -+ HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | grep -v '/type-level\.haddock' | sort` - for HADDOCK_FILE in $HADDOCK_FILES - do - NAME_VERSION=`echo "$HADDOCK_FILE" | sed 's#/.*##'` diff --git a/ghc-powerpc-linker-mmap.patch b/ghc-powerpc-linker-mmap.patch deleted file mode 100644 index df0d5ff..0000000 --- a/ghc-powerpc-linker-mmap.patch +++ /dev/null @@ -1,34 +0,0 @@ -diff -up ghc-7.0.2/rts/Linker.c.fix-powerpc ghc-7.0.2/rts/Linker.c ---- ghc-7.0.2/rts/Linker.c.fix-powerpc 2011-02-28 19:10:08.000000000 +0100 -+++ ghc-7.0.2/rts/Linker.c 2011-04-25 22:20:10.781092305 +0200 -@@ -70,11 +70,12 @@ - #include - #endif - --#if defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ -- defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ -- defined(openbsd_HOST_OS ) || \ -- ( defined(darwin_HOST_OS ) && !defined(powerpc_HOST_ARCH) ) --/* Don't use mmap on powerpc-apple-darwin as mmap doesn't support -+#if !defined(powerpc_HOST_ARCH) && \ -+ ( defined(linux_HOST_OS ) || defined(freebsd_HOST_OS) || \ -+ defined(dragonfly_HOST_OS) || defined(netbsd_HOST_OS ) || \ -+ defined(openbsd_HOST_OS ) || defined(darwin_HOST_OS ) || \ -+ defined(kfreebsdgnu_HOST_OS) ) -+/* Don't use mmap on powerpc_HOST_ARCH as mmap doesn't support - * reallocating but we need to allocate jump islands just after each - * object images. Otherwise relative branches to jump islands can fail - * due to 24-bits displacement overflow. -@@ -2436,7 +2437,11 @@ static void ocFlushInstructionCacheFrom( - static void ocFlushInstructionCache( ObjectCode *oc ) - { - /* The main object code */ -- ocFlushInstructionCacheFrom(oc->image + oc->misalignment, oc->fileSize); -+ ocFlushInstructionCacheFrom(oc->image -+#ifdef darwin_HOST_OS -+ + oc->misalignment -+#endif -+ , oc->fileSize); - - /* Jump Islands */ - ocFlushInstructionCacheFrom(oc->symbol_extras, sizeof(SymbolExtra) * oc->n_symbol_extras); diff --git a/ghc-powerpc-pthread.patch b/ghc-powerpc-pthread.patch deleted file mode 100644 index d317ff7..0000000 --- a/ghc-powerpc-pthread.patch +++ /dev/null @@ -1,18 +0,0 @@ -diff -up ghc-7.0.2/aclocal.m4.pthread ghc-7.0.2/aclocal.m4 ---- ghc-7.0.2/aclocal.m4.pthread 2011-02-28 13:10:03.000000000 -0500 -+++ ghc-7.0.2/aclocal.m4 2011-04-20 07:12:36.489772545 -0400 -@@ -1385,7 +1385,7 @@ AC_MSG_NOTICE(Building in-tree ghc-pwd) - dnl except we don't want to have to know what make is called. Sigh. - rm -rf utils/ghc-pwd/dist-boot - mkdir utils/ghc-pwd/dist-boot -- if ! "$WithGhc" -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd -+ if ! "$WithGhc" -optl-pthread -v0 -no-user-package-conf -hidir utils/ghc-pwd/dist-boot -odir utils/ghc-pwd/dist-boot -stubdir utils/ghc-pwd/dist-boot --make utils/ghc-pwd/Main.hs -o utils/ghc-pwd/dist-boot/ghc-pwd - then - AC_MSG_ERROR([Building ghc-pwd failed]) - fi -diff -up ghc-7.0.2/ghc/ghc.wrapper.pthread ghc-7.0.2/ghc/ghc.wrapper ---- ghc-7.0.2/ghc/ghc.wrapper.pthread 2011-04-20 09:58:50.307894773 -0400 -+++ ghc-7.0.2/ghc/ghc.wrapper 2011-04-20 09:59:14.477894370 -0400 -@@ -1 +1 @@ --exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" ${1+"$@"} -+exec "$executablename" -B"$topdir" -pgmc "$pgmgcc" -pgma "$pgmgcc" -pgml "$pgmgcc" -pgmP "$pgmgcc -E -undef -traditional" -optl-pthread ${1+"$@"} diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch index 304bcb9..fb6d90a 100644 --- a/ghc-use-system-libffi.patch +++ b/ghc-use-system-libffi.patch @@ -1,10 +1,10 @@ This patch could be replaced by a configure call if http://hackage.haskell.org/trac/ghc/ticket/5743 were fixed. -Index: ghc-7.4.0.20111219/rts/package.conf.in +Index: ghc-7.6.1/rts/package.conf.in =================================================================== ---- ghc-7.4.0.20111219.orig/rts/package.conf.in 2011-12-21 23:21:03.000000000 +0100 -+++ ghc-7.4.0.20111219/rts/package.conf.in 2011-12-21 23:21:04.000000000 +0100 +--- ghc-7.6.1.orig/rts/package.conf.in 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/rts/package.conf.in 2012-10-08 13:06:55.167887121 +0200 @@ -24,8 +24,9 @@ hs-libraries: "HSrts" @@ -16,48 +16,38 @@ Index: ghc-7.4.0.20111219/rts/package.conf.in #endif #ifdef HAVE_LIBRT , "rt" -Index: ghc-7.4.0.20111219/ghc.mk +Index: ghc-7.6.1/ghc.mk =================================================================== ---- ghc-7.4.0.20111219.orig/ghc.mk 2011-12-21 23:21:03.000000000 +0100 -+++ ghc-7.4.0.20111219/ghc.mk 2011-12-21 23:21:04.000000000 +0100 -@@ -579,7 +579,6 @@ - driver/ghci \ +--- ghc-7.6.1.orig/ghc.mk 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/ghc.mk 2012-10-08 13:06:55.171887120 +0200 +@@ -600,7 +600,6 @@ + $(MAYBE_GHCI) \ driver/ghc \ driver/haddock \ - libffi \ includes \ rts -Index: ghc-7.4.0.20111219/rts/ghc.mk +Index: ghc-7.6.1/rts/ghc.mk =================================================================== ---- ghc-7.4.0.20111219.orig/rts/ghc.mk 2011-12-21 19:56:29.000000000 +0100 -+++ ghc-7.4.0.20111219/rts/ghc.mk 2011-12-21 23:23:52.000000000 +0100 -@@ -86,8 +86,7 @@ - ALL_RTS_DEF_LIBNAMES = base ghc-prim - ALL_RTS_DEF_LIBS = \ - rts/dist/build/win32/libHSbase.dll.a \ -- rts/dist/build/win32/libHSghc-prim.dll.a \ -- libffi/build/inst/lib/libffi.dll.a -+ rts/dist/build/win32/libHSghc-prim.dll.a - - # -- import libs for the regular Haskell libraries - define make-importlib-def # args $1 = lib name -@@ -172,12 +171,12 @@ +--- ghc-7.6.1.orig/rts/ghc.mk 2012-09-04 19:10:15.000000000 +0200 ++++ ghc-7.6.1/rts/ghc.mk 2012-10-08 13:08:52.019882891 +0200 +@@ -177,12 +177,12 @@ # Making a shared library for the RTS. ifneq "$$(findstring dyn, $1)" "" - ifeq "$$(HOSTPLATFORM)" "i386-unknown-mingw32" --$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/libffi-5.dll + ifeq "$$(HostOS_CPP)" "mingw32" +-$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/$$(LIBFFI_DLL) +$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ - -no-auto-link-packages -Lrts/dist/build -lffi-5 `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ + -no-auto-link-packages -Lrts/dist/build -l$(LIBFFI_WINDOWS_LIB) `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ else -$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend rts/dist/build/libffi$$(soext) +$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend "$$(RM)" $$(RM_OPTS) $$@ "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ -no-auto-link-packages -Lrts/dist/build -lffi `cat rts/libs.depend` $$(rts_$1_OBJS) \ -@@ -188,9 +187,9 @@ +@@ -193,9 +193,9 @@ endif endif else @@ -69,12 +59,12 @@ Index: ghc-7.4.0.20111219/rts/ghc.mk $$(AR_OPTS_STAGE1) $$(EXTRA_AR_ARGS_STAGE1) $$@ endif -@@ -504,10 +503,8 @@ +@@ -509,10 +509,8 @@ # installing INSTALL_LIBS += $(ALL_RTS_LIBS) -INSTALL_LIBS += $(wildcard rts/dist/build/libffi$(soext)*) --INSTALL_LIBS += $(wildcard rts/dist/build/libffi-5.dll) +-INSTALL_LIBS += $(wildcard rts/dist/build/$(LIBFFI_DLL)) -install: install_libffi_headers +install: diff --git a/ghc.spec b/ghc.spec index 988509c..ec3af0c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_testsuite 1 -#%%global without_haddock 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_testsuite 1 +%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -24,25 +24,35 @@ Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.4.2 +Version: 7.6.3 # Since library subpackages are versioned: -# - release can only be reset if all library versions get bumped simultaneously -# (eg for a major release) -# - minor release numbers should be incremented monotonically -Release: 11%{?dist} +# - release can only be reset if *all* library versions get bumped simultaneously +# (sometimes after a major release) +# - minor release numbers for a branch should be incremented monotonically +Release: 11.9%{?dist} Summary: Glasgow Haskell Compiler -# fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x -# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -ExcludeArch: sparc64 + License: %BSDHaskellReport +URL: http://haskell.org/ghc/ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index -URL: http://haskell.org/ghc/ +# absolute haddock path (was for html/libraries -> libraries) +Patch1: ghc-gen_contents_index-haddock-path.patch +# fedora does not allow copy libraries +Patch4: ghc-use-system-libffi.patch +# add libffi include dir to ghc wrapper for archs using gcc/llc +Patch10: ghc-wrapper-libffi-include.patch +# disable building HS*.o libs for ghci +Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch + +# fedora ghc has been bootstrapped on +# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x +# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros +ExcludeArch: sparc64 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 Obsoletes: ghc-dph-prim-interface < 0.5, ghc-dph-prim-interface-devel < 0.5, ghc-dph-interface-prim-prof < 0.5 @@ -53,7 +63,7 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -BuildRequires: ghc-rpm-macros >= 0.91 +BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -73,31 +83,10 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif -%ifarch armv7hl -BuildRequires: autoconf -%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-doc-index = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} -# absolute haddock path (was for html/libraries -> libraries) -Patch1: ghc-6.12.1-gen_contents_index-haddock-path.patch -# type-level too big so skip it in gen_contents_index -Patch2: ghc-gen_contents_index-type-level.patch -# fedora does not allow copy libraries -Patch4: ghc-use-system-libffi.patch -Patch7: ghc-powerpc-pthread.patch -# http://hackage.haskell.org/trac/ghc/ticket/4999 -Patch8: ghc-powerpc-linker-mmap.patch -# fix dynamic linking of executables using Template Haskell -Patch9: Cabal-fix-dynamic-exec-for-TH.patch -# add libffi include dir to ghc wrapper for archs using gcc/llc -Patch10: ghc-wrapper-libffi-include.patch -# latest arm hf patch -Patch11: ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch -# disable building HS*.o libs for ghci -Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch -Patch17: ghc-7.4-silence-gen_contents_index.patch %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -161,31 +150,30 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_lib_subpackage Cabal 1.14.0 -%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.5.1.0 -%ghc_lib_subpackage binary 0.5.1.0 -%ghc_lib_subpackage bytestring 0.9.2.1 -%ghc_lib_subpackage -l %BSDHaskellReport containers 0.4.2.1 -%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport directory 1.1.0.2 -%ghc_lib_subpackage -l %BSDHaskellReport extensible-exceptions 0.1.1.4 -%ghc_lib_subpackage filepath 1.3.0.0 +%ghc_lib_subpackage Cabal 1.16.0 +%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.1 +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.6.0.1 +%ghc_lib_subpackage binary 0.5.1.1 +%ghc_lib_subpackage bytestring 0.10.0.2 +%ghc_lib_subpackage -l %BSDHaskellReport containers 0.5.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.1 +%ghc_lib_subpackage -l %BSDHaskellReport directory 1.2.0.1 +%ghc_lib_subpackage filepath 1.3.0.1 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.0.1 -%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.1 -%ghc_lib_subpackage hoopl 3.8.7.3 -%ghc_lib_subpackage hpc 0.5.1.1 -%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.4 -%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.0 +%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.1.0 +%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.2 +%ghc_lib_subpackage hoopl 3.9.0.0 +%ghc_lib_subpackage hpc 0.6.0.0 +%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.5 +%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.1 %ghc_lib_subpackage pretty 1.1.1.0 -%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.1 -%ghc_lib_subpackage template-haskell 2.7.0.0 -%ghc_lib_subpackage time 1.4 -%ghc_lib_subpackage unix 2.5.1.1 +%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.2 +%ghc_lib_subpackage template-haskell 2.8.0.0 +%ghc_lib_subpackage time 1.4.0.1 +%ghc_lib_subpackage unix 2.6.0.1 %endif %global version %{ghc_version_override} @@ -206,37 +194,28 @@ Obsoletes: ghc-libs < 7.0.1-3 This is a meta-package for all the development library packages in GHC except the ghc library, which is installed by the toplevel ghc metapackage. + %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} -# tweaks to gen_contents_index +# gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -%patch2 -p1 -%patch17 -p1 # make sure we don't use these -rm -r ghc-tarballs/{mingw,perl} +rm -r ghc-tarballs/{mingw*,perl} # use system libffi %patch4 -p1 -b .libffi rm -r ghc-tarballs/libffi mkdir -p rts/dist/build ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build -%patch9 -p1 -b .orig - %ifnarch %{ix86} x86_64 %patch10 -p1 -b .10-ffi %endif -# ARM patches -%ifarch armv7hl -# touches aclocal.m4 -%patch11 -p1 -b .arm -autoreconf -%endif - %patch12 -p1 -b .orig + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc @@ -261,6 +240,7 @@ export CFLAGS="${CFLAGS:-%optflags}" make %{?_smp_mflags} + %install make DESTDIR=%{buildroot} install @@ -268,21 +248,19 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name%{?ghc_without_shared:-devel}.files +echo "%doc libraries/$name/LICENSE" >> ghc-$name.files done # ghc-base should own ghclibdir -echo "%dir %{ghclibdir}" >> ghc-base%{?ghc_without_shared:-devel}.files +echo "%dir %{ghclibdir}" >> ghc-base.files %ghc_gen_filelists bin-package-db 0.0.0.0 %ghc_gen_filelists ghc %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.2.0.0 -%ghc_gen_filelists integer-gmp 0.4.0.0 +%ghc_gen_filelists ghc-prim 0.3.0.0 +%ghc_gen_filelists integer-gmp 0.5.0.0 %define merge_filelist()\ -%if %{undefined ghc_without_shared}\ cat ghc-%1.files >> ghc-%2.files\ -%endif\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files @@ -318,6 +296,7 @@ mkdir -p %{buildroot}%{_localstatedir}/lib/ghc install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index %endif + %check # stolen from ghc6/debian/rules: # Do some very simple tests that the compiler actually works @@ -343,6 +322,7 @@ rm testghc/* make test %endif + %post compiler # Alas, GHC, Hugs, and nhc all come with different set of tools in # addition to a runFOO: @@ -367,6 +347,7 @@ if [ "$1" = 0 ]; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi + %files %files compiler @@ -381,7 +362,7 @@ fi %{_bindir}/hpc %ghost %{_bindir}/hsc2hs %{_bindir}/hsc2hs-ghc -%{_bindir}/runghc +%{_bindir}/runghc* %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc %{ghclibdir}/ghc @@ -417,9 +398,10 @@ fi %dir %{ghcdocbasedir}/libraries %{ghcdocbasedir}/libraries/frames.html %{ghcdocbasedir}/libraries/gen_contents_index -%{ghcdocbasedir}/libraries/hscolour.css +%{ghcdocbasedir}/libraries/hslogo-16.png %{ghcdocbasedir}/libraries/ocean.css %{ghcdocbasedir}/libraries/prologue.txt +%{ghcdocbasedir}/libraries/synopsis.png %{ghcdocbasedir}/index.html %ghost %{ghcdocbasedir}/libraries/doc-index*.html %ghost %{ghcdocbasedir}/libraries/haddock-util.js @@ -436,7 +418,20 @@ fi %files libraries + %changelog +* Mon Apr 22 2013 Jens Petersen - 7.6.3-11.9 +- bootstrap 7.6.3, see release notes: + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-1.html + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-2.html + http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-3.html +- all library versions bumped except pretty +- Cabal-fix-dynamic-exec-for-TH.patch, + ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch, and + ghc-7.4-silence-gen_contents_index.patch are no longer needed +- build with ghc-rpm-macros-extra +- no longer filter type-level package from haddock index + * Tue Feb 5 2013 Jens Petersen - 7.4.2-11 - ghclibdir should be owned at runtime by ghc-base instead of ghc-compiler (thanks Michael Scherer, #907671) diff --git a/sources b/sources index 46b12d9..40df58f 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -267462db5c5a7c245fb26361b77007c4 ghc-7.4.2-src.tar.bz2 -528005749c761fe6c12a0079bd84fb90 ghc-7.4.2-testsuite.tar.bz2 +986d1f90ca30d60f7b2820d75c6b8ea7 ghc-7.6.3-src.tar.bz2 +66aa6177a31cc4b9d7eeb55cb1514918 ghc-7.6.3-testsuite.tar.bz2 From 5ff993dce3c7b9c05dcb01a346396c2650939c66 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 23 Apr 2013 19:52:22 +0900 Subject: [PATCH 347/530] only require ghc-doc-index if we package it --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index ec3af0c..e5ab498 100644 --- a/ghc.spec +++ b/ghc.spec @@ -84,7 +84,9 @@ BuildRequires: python BuildRequires: llvm >= 3.0 %endif Requires: ghc-compiler = %{version}-%{release} +%if %{undefined without_haddock} Requires: ghc-doc-index = %{version}-%{release} +%endif Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} From 6643079e5d23b8790693ce2c7650de4bbfc4c54b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 6 Jun 2013 11:58:43 +0900 Subject: [PATCH 348/530] production build with BuildFlavour perf; obsolete process-leksah --- ghc.spec | 11 +++++++++++ 1 file changed, 11 insertions(+) diff --git a/ghc.spec b/ghc.spec index e5ab498..6ba7171 100644 --- a/ghc.spec +++ b/ghc.spec @@ -172,7 +172,9 @@ documention. %ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.5 %ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.1 %ghc_lib_subpackage pretty 1.1.1.0 +%define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 %ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.2 +%undefine ghc_pkg_obsoletes %ghc_lib_subpackage template-haskell 2.8.0.0 %ghc_lib_subpackage time 1.4.0.1 %ghc_lib_subpackage unix 2.6.0.1 @@ -222,6 +224,13 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF +%if %{undefined ghc_bootstrapping} +%ifnarch armv7hl armv5tel +BuildFlavour = perf +%else +BuildFlavour = perf-llvm +%endif +%endif GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO @@ -433,6 +442,8 @@ fi ghc-7.4-silence-gen_contents_index.patch are no longer needed - build with ghc-rpm-macros-extra - no longer filter type-level package from haddock index +- process obsoletes process-leksah +- do production build with BuildFlavour perf (#880135) * Tue Feb 5 2013 Jens Petersen - 7.4.2-11 - ghclibdir should be owned at runtime by ghc-base instead of ghc-compiler From 1f0e92321d0251c6782cde1d6322c25e1f82c9ef Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 12 Jun 2013 11:43:49 +0900 Subject: [PATCH 349/530] reinstate and refresh Cabal-fix-dynamic-exec-for-TH.patch --- Cabal-fix-dynamic-exec-for-TH.patch | 23 +++++++++++++++++++++++ ghc.spec | 8 ++++++-- 2 files changed, 29 insertions(+), 2 deletions(-) create mode 100644 Cabal-fix-dynamic-exec-for-TH.patch diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch new file mode 100644 index 0000000..382b343 --- /dev/null +++ b/Cabal-fix-dynamic-exec-for-TH.patch @@ -0,0 +1,23 @@ +--- ghc-7.6.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs~ 2013-04-19 06:32:04.000000000 +0900 ++++ ghc-7.6.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs 2013-06-12 11:35:39.832840754 +0900 +@@ -837,6 +837,8 @@ + + dynamicOpts = vanillaOpts `mappend` mempty { + ghcOptDynamic = toFlag True, ++ ghcOptHiSuffix = toFlag "dyn_hi", ++ ghcOptObjSuffix = toFlag "dyn_o", + ghcOptExtra = ghcSharedOptions exeBi + } + +@@ -855,9 +857,9 @@ + -- with profiling. This is because the code that TH needs to + -- run at compile time needs to be the vanilla ABI so it can + -- be loaded up and run by the compiler. +- when (withProfExe lbi && ++ when ((withProfExe lbi || withDynExe lbi) && + EnableExtension TemplateHaskell `elem` allExtensions exeBi) $ +- runGhcProg exeProfOpts { ghcOptNoLink = toFlag True } ++ runGhcProg staticOpts { ghcOptNoLink = toFlag True } + + runGhcProg exeOpts { ghcOptOutputFile = toFlag (targetDir exeNameReal) } + diff --git a/ghc.spec b/ghc.spec index 6ba7171..33159df 100644 --- a/ghc.spec +++ b/ghc.spec @@ -41,9 +41,11 @@ Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) -Patch1: ghc-gen_contents_index-haddock-path.patch +Patch1: ghc-gen_contents_index-haddock-path.patch # fedora does not allow copy libraries -Patch4: ghc-use-system-libffi.patch +Patch4: ghc-use-system-libffi.patch +# fix dynamic linking of executables using Template Haskell +Patch9: Cabal-fix-dynamic-exec-for-TH.patch # add libffi include dir to ghc wrapper for archs using gcc/llc Patch10: ghc-wrapper-libffi-include.patch # disable building HS*.o libs for ghci @@ -213,6 +215,8 @@ rm -r ghc-tarballs/libffi mkdir -p rts/dist/build ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build +%patch9 -p1 -b .orig + %ifnarch %{ix86} x86_64 %patch10 -p1 -b .10-ffi %endif From dbc5d438ab189a9335f5bb52a8f139041634349d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 12 Jun 2013 12:14:35 +0900 Subject: [PATCH 350/530] correct the option list name in the Cabal dynexe TH patch --- Cabal-fix-dynamic-exec-for-TH.patch | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch index 382b343..fb95f83 100644 --- a/Cabal-fix-dynamic-exec-for-TH.patch +++ b/Cabal-fix-dynamic-exec-for-TH.patch @@ -17,7 +17,7 @@ + when ((withProfExe lbi || withDynExe lbi) && EnableExtension TemplateHaskell `elem` allExtensions exeBi) $ - runGhcProg exeProfOpts { ghcOptNoLink = toFlag True } -+ runGhcProg staticOpts { ghcOptNoLink = toFlag True } ++ runGhcProg vanillaOpts { ghcOptNoLink = toFlag True } runGhcProg exeOpts { ghcOptOutputFile = toFlag (targetDir exeNameReal) } From 1d488d5a3172bd52b2bca7711e1e17b819533c99 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 20 Jun 2013 14:21:18 +0900 Subject: [PATCH 351/530] bump release to integer 12 --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 33159df..17160d1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 11.9%{?dist} +Release: 12%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -435,7 +435,7 @@ fi %changelog -* Mon Apr 22 2013 Jens Petersen - 7.6.3-11.9 +* Mon Apr 22 2013 Jens Petersen - 7.6.3-12 - bootstrap 7.6.3, see release notes: http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-1.html http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-2.html From 44f0e24aa67e7acf0e02eb0045e052d743ddf8ea Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 20 Jun 2013 17:41:31 +0900 Subject: [PATCH 352/530] production build --- ghc.spec | 18 +++++++++++------- 1 file changed, 11 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 17160d1..de61d3d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_testsuite 1 -%global without_haddock 1 +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_testsuite 1 +#%%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 12%{?dist} +Release: 13%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -435,11 +435,15 @@ fi %changelog -* Mon Apr 22 2013 Jens Petersen - 7.6.3-12 -- bootstrap 7.6.3, see release notes: +* Thu Jun 20 2013 Jens Petersen - 7.6.3-13 +- production perf -O2 build +- see release notes: http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-1.html http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-2.html http://www.haskell.org/ghc/docs/7.6.3/html/users_guide/release-7-6-3.html + +* Thu Jun 20 2013 Jens Petersen - 7.6.3-12 +- bootstrap 7.6.3 - all library versions bumped except pretty - Cabal-fix-dynamic-exec-for-TH.patch, ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch, and From 5a78a2efb54d2390c8f75448f7e0760b516fe452 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 25 Jun 2013 16:56:39 +0900 Subject: [PATCH 353/530] fix compilation with llvm-3.3 --- ghc-llvmCodeGen-empty-array.patch | 46 +++++++++++++++++++++++++++++++ ghc.spec | 10 ++++++- 2 files changed, 55 insertions(+), 1 deletion(-) create mode 100644 ghc-llvmCodeGen-empty-array.patch diff --git a/ghc-llvmCodeGen-empty-array.patch b/ghc-llvmCodeGen-empty-array.patch new file mode 100644 index 0000000..5dc3e96 --- /dev/null +++ b/ghc-llvmCodeGen-empty-array.patch @@ -0,0 +1,46 @@ +commit db9b63105a541e4ad3f9c55e2cfadf716445ab87 +Author: Geoffrey Mainland +Date: Wed Jun 12 14:31:49 2013 +0100 + + Avoid generating empty llvm.used definitions. + + LLVM 3.3rc3 complains when the llvm.used global is an empty array, so don't + define llvm.used at all when it would be empty. + + Modified compiler/llvmGen/LlvmCodeGen.hs +diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs +index a157a25..4f2bded 100644 +--- a/compiler/llvmGen/LlvmCodeGen.hs ++++ b/compiler/llvmGen/LlvmCodeGen.hs +@@ -117,19 +117,19 @@ cmmProcLlvmGens :: DynFlags -> BufHandle -> UniqSupply -> LlvmEnv -> [RawCmmDecl + -> [[LlvmVar]] -- ^ info tables that need to be marked as 'used' + -> IO () + +-cmmProcLlvmGens _ _ _ _ [] _ [] +- = return () +- + cmmProcLlvmGens dflags h _ _ [] _ ivars +- = let ivars' = concat ivars +- cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr +- ty = (LMArray (length ivars') i8Ptr) +- usedArray = LMStaticArray (map cast ivars') ty +- lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending +- (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray) +- in Prt.bufLeftRender h $ {-# SCC "llvm_used_ppr" #-} +- withPprStyleDoc dflags (mkCodeStyle CStyle) $ +- pprLlvmData ([lmUsed], []) ++ | null ivars' = return () ++ | otherwise = Prt.bufLeftRender h $ ++ {-# SCC "llvm_used_ppr" #-} ++ withPprStyleDoc dflags (mkCodeStyle CStyle) $ ++ pprLlvmData ([lmUsed], []) ++ where ++ ivars' = concat ivars ++ cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr ++ ty = (LMArray (length ivars') i8Ptr) ++ usedArray = LMStaticArray (map cast ivars') ty ++ lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending ++ (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray) + + cmmProcLlvmGens dflags h us env ((CmmData _ _) : cmms) count ivars + = cmmProcLlvmGens dflags h us env cmms count ivars diff --git a/ghc.spec b/ghc.spec index de61d3d..3951741 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 13%{?dist} +Release: 14%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -50,6 +50,8 @@ Patch9: Cabal-fix-dynamic-exec-for-TH.patch Patch10: ghc-wrapper-libffi-include.patch # disable building HS*.o libs for ghci Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch +# fix compilation with llvm-3.3 +Patch13: ghc-llvmCodeGen-empty-array.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -223,6 +225,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch12 -p1 -b .orig +%patch13 -p1 -b .orig + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms @@ -435,6 +439,10 @@ fi %changelog +* Tue Jun 25 2013 Jens Petersen - 7.6.3-14 +- fix compilation with llvm-3.3 (#977652) + see http://hackage.haskell.org/trac/ghc/ticket/7996 + * Thu Jun 20 2013 Jens Petersen - 7.6.3-13 - production perf -O2 build - see release notes: From cbe15a3bdfac62b71dffdcbf4a905f0323e408a9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 10 Jul 2013 11:07:23 +0900 Subject: [PATCH 354/530] turn off executable stack flag in executables (#973512) - reported by Dhiru Kholia - upstream patch by Edward Zhang: see http://ghc.haskell.org/trac/ghc/ticket/703 and https://github.com/ghc/ghc/commit/08a38628f29df63ac842f4d083efb414f42d7bff - this affects both ghc 7.4 and 7.6 --- ghc-NCG-no-execstack.patch | 32 ++++++++++++++++++++++++++++++++ ghc.spec | 13 +++++++++---- 2 files changed, 41 insertions(+), 4 deletions(-) create mode 100644 ghc-NCG-no-execstack.patch diff --git a/ghc-NCG-no-execstack.patch b/ghc-NCG-no-execstack.patch new file mode 100644 index 0000000..40b6ba6 --- /dev/null +++ b/ghc-NCG-no-execstack.patch @@ -0,0 +1,32 @@ +commit 08a38628f29df63ac842f4d083efb414f42d7bff +Author: Edward Z. Yang +Date: Tue Jul 9 00:01:43 2013 -0700 + + Disable executable stack for the linker note, fixing #703 (again) + + Signed-off-by: Edward Z. Yang + + Modified compiler/main/DriverPipeline.hs +diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs +index 67377e6..26425ae 100644 +--- a/compiler/main/DriverPipeline.hs ++++ b/compiler/main/DriverPipeline.hs +@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do + text elfSectionNote, + text "\n", + +- text "\t.ascii \"", info', text "\"\n" ] ++ text "\t.ascii \"", info', text "\"\n", ++ ++ -- ALL generated assembly must have this section to disable ++ -- executable stacks. See also ++ -- compiler/nativeGen/AsmCodeGen.lhs for another instance ++ -- where we need to do this. ++ (if platformHasGnuNonexecStack (targetPlatform dflags) ++ then text ".section .note.GNU-stack,\"\",@progbits\n" ++ else empty) ++ ++ ] + where + info' = text $ escape info + diff --git a/ghc.spec b/ghc.spec index 3951741..af89833 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 14%{?dist} +Release: 15%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -52,6 +52,8 @@ Patch10: ghc-wrapper-libffi-include.patch Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch # fix compilation with llvm-3.3 Patch13: ghc-llvmCodeGen-empty-array.patch +# disable executable stack +Patch14: ghc-NCG-no-execstack.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -224,8 +226,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %endif %patch12 -p1 -b .orig - %patch13 -p1 -b .orig +%patch14 -p1 -b .orig %build @@ -439,6 +441,10 @@ fi %changelog +* Wed Jul 10 2013 Jens Petersen - 7.6.3-15 +- turn off executable stack flag in executables (#973512) + (thanks Edward Zhang for upstream patch and Dhiru Kholia for report) + * Tue Jun 25 2013 Jens Petersen - 7.6.3-14 - fix compilation with llvm-3.3 (#977652) see http://hackage.haskell.org/trac/ghc/ticket/7996 @@ -453,8 +459,7 @@ fi * Thu Jun 20 2013 Jens Petersen - 7.6.3-12 - bootstrap 7.6.3 - all library versions bumped except pretty -- Cabal-fix-dynamic-exec-for-TH.patch, - ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch, and +- ghc-7.4-add-support-for-ARM-hard-float-ABI-fixes-5914.patch, and ghc-7.4-silence-gen_contents_index.patch are no longer needed - build with ghc-rpm-macros-extra - no longer filter type-level package from haddock index From 6ad25889ec4a7e2ff1123ce08001a8cb6736a9ad Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 11 Jul 2013 17:29:11 +0900 Subject: [PATCH 355/530] Revert "turn off executable stack flag in executables (#973512)" While it seems to fix the flag for intermediate object files final executables still seems to have the flag set somehow. Further the patch apparently changed the ABI of the ghc library. --- ghc.spec | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index af89833..ca0ac89 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 15%{?dist} +Release: 16%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -52,8 +52,6 @@ Patch10: ghc-wrapper-libffi-include.patch Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch # fix compilation with llvm-3.3 Patch13: ghc-llvmCodeGen-empty-array.patch -# disable executable stack -Patch14: ghc-NCG-no-execstack.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -226,8 +224,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %endif %patch12 -p1 -b .orig + %patch13 -p1 -b .orig -%patch14 -p1 -b .orig %build @@ -441,6 +439,10 @@ fi %changelog +* Thu Jul 11 2013 Jens Petersen - 7.6.3-16 +- revert the executable stack patch since it didn't fully fix the problem + and yet changed the ghc library hash + * Wed Jul 10 2013 Jens Petersen - 7.6.3-15 - turn off executable stack flag in executables (#973512) (thanks Edward Zhang for upstream patch and Dhiru Kholia for report) From 35375ea0a510acc6758bf393a2e1eee28a76ded4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jul 2013 11:20:37 +0900 Subject: [PATCH 356/530] temporary bootstrap build for ARM with llvm-3.3 fix --- ghc.spec | 19 +++++++------------ 1 file changed, 7 insertions(+), 12 deletions(-) diff --git a/ghc.spec b/ghc.spec index ca0ac89..676ed0d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_testsuite 1 -#%%global without_haddock 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_testsuite 1 +%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 16%{?dist} +Release: 14.1%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -439,13 +439,8 @@ fi %changelog -* Thu Jul 11 2013 Jens Petersen - 7.6.3-16 -- revert the executable stack patch since it didn't fully fix the problem - and yet changed the ghc library hash - -* Wed Jul 10 2013 Jens Petersen - 7.6.3-15 -- turn off executable stack flag in executables (#973512) - (thanks Edward Zhang for upstream patch and Dhiru Kholia for report) +* Wed Jul 24 2013 Jens Petersen - 7.6.3-14.1 +- temporary bootstrap build for ARM with llvm-3.3 fix * Tue Jun 25 2013 Jens Petersen - 7.6.3-14 - fix compilation with llvm-3.3 (#977652) From 47c247655af3bc18dc19dd3431d5d20aedb72092 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jul 2013 14:18:09 +0900 Subject: [PATCH 357/530] Revert "temporary bootstrap build for ARM with llvm-3.3 fix" This reverts commit a044dc3f8af30144c9639d83d2c6db8f2895a1a6. --- ghc.spec | 19 ++++++++++++------- 1 file changed, 12 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 676ed0d..ca0ac89 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,10 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_testsuite 1 -%global without_haddock 1 +#%%global ghc_bootstrapping 1 +#%%{?ghc_bootstrap} +#%%global without_testsuite 1 +#%%global without_haddock 1 # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 14.1%{?dist} +Release: 16%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -439,8 +439,13 @@ fi %changelog -* Wed Jul 24 2013 Jens Petersen - 7.6.3-14.1 -- temporary bootstrap build for ARM with llvm-3.3 fix +* Thu Jul 11 2013 Jens Petersen - 7.6.3-16 +- revert the executable stack patch since it didn't fully fix the problem + and yet changed the ghc library hash + +* Wed Jul 10 2013 Jens Petersen - 7.6.3-15 +- turn off executable stack flag in executables (#973512) + (thanks Edward Zhang for upstream patch and Dhiru Kholia for report) * Tue Jun 25 2013 Jens Petersen - 7.6.3-14 - fix compilation with llvm-3.3 (#977652) From 7e87c6a1e6b56adf0d99348662057d4c20d940d9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jul 2013 18:08:02 +0900 Subject: [PATCH 358/530] silence warnings about unsupported llvm version (> 3.1) on ARM +You are using a new version of LLVM that hasn't been tested yet! +We will try though... (ghc-7.6 only officially supports 2.8 <= llvm <= 3.1) --- ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch | 11 +++++++++++ ghc.spec | 11 ++++++++++- 2 files changed, 21 insertions(+), 1 deletion(-) create mode 100644 ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch diff --git a/ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch b/ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch new file mode 100644 index 0000000..d48abd4 --- /dev/null +++ b/ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch @@ -0,0 +1,11 @@ +--- ghc-7.6.3/compiler/llvmGen/LlvmCodeGen/Base.hs~ 2013-04-19 06:22:46.000000000 +0900 ++++ ghc-7.6.3/compiler/llvmGen/LlvmCodeGen/Base.hs 2013-07-24 17:05:06.491900335 +0900 +@@ -151,7 +151,7 @@ + minSupportLlvmVersion = 28 + + maxSupportLlvmVersion :: LlvmVersion +-maxSupportLlvmVersion = 31 ++maxSupportLlvmVersion = 33 + + -- ---------------------------------------------------------------------------- + -- * Environment Handling diff --git a/ghc.spec b/ghc.spec index ca0ac89..986d02b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 16%{?dist} +Release: 17%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -52,6 +52,8 @@ Patch10: ghc-wrapper-libffi-include.patch Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch # fix compilation with llvm-3.3 Patch13: ghc-llvmCodeGen-empty-array.patch +# stop warnings about unsupported version of llvm +Patch14: ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -227,6 +229,10 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch13 -p1 -b .orig +%ifarch armv7hl armv5tel +%patch14 -p1 -b .orig +%endif + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms @@ -439,6 +445,9 @@ fi %changelog +* Wed Jul 24 2013 Jens Petersen - 7.6.3-17 +- silence warnings about unsupported llvm version (> 3.1) on ARM + * Thu Jul 11 2013 Jens Petersen - 7.6.3-16 - revert the executable stack patch since it didn't fully fix the problem and yet changed the ghc library hash From f52785234ae1993fdad3b96954755b66bf56bb42 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 29 Jul 2013 11:35:56 +0900 Subject: [PATCH 359/530] follow http://fedoraproject.org/wiki/Packaging:CronFiles MIME-Version: 1.0 Content-Type: text/plain; charset=UTF-8 Content-Transfer-Encoding: 8bit thanks Jóhann Guðmundsson --- ghc.spec | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 986d02b..dc2e8f5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -29,7 +29,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 17%{?dist} +Release: 18%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -141,6 +141,7 @@ To install all of ghc, install the ghc base package. Summary: GHC library development documentation indexing License: BSD Requires: ghc-compiler = %{version}-%{release} +Requires: crontabs %description doc-index The package provides a cronjob for re-indexing installed library development @@ -438,13 +439,17 @@ fi %if %{undefined without_haddock} %files doc-index -%{_sysconfdir}/cron.hourly/ghc-doc-index +%config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index %endif %files libraries %changelog +* Sat Jul 27 2013 Jóhann B. Guðmundsson - 7.6.3-18 +- ghc-doc-index requires crontabs and mark cron file config noreplace + (http://fedoraproject.org/wiki/Packaging:CronFiles) + * Wed Jul 24 2013 Jens Petersen - 7.6.3-17 - silence warnings about unsupported llvm version (> 3.1) on ARM From 0d58db635842e7e6b5a57975ebe84366a7b4e40e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 29 Oct 2013 14:59:08 +0900 Subject: [PATCH 360/530] bootstrap build to fix hangs on 64bit bigendian - rts hang patch from Gustavo Luiz Duarte (#989593) - generate and ship library doc index for ghc bundled libraries - build with utf8 encoding (needed for verbose ghc output and makes better sense anyway) - change ghc-cabal to make library html docdirs unversioned --- ghc-64bit-bigendian-rts-hang-989593.patch | 11 +++++ ghc-cabal-unversion-docdir.patch | 13 ++++++ ghc.spec | 53 +++++++++++++++++++---- 3 files changed, 69 insertions(+), 8 deletions(-) create mode 100644 ghc-64bit-bigendian-rts-hang-989593.patch create mode 100644 ghc-cabal-unversion-docdir.patch diff --git a/ghc-64bit-bigendian-rts-hang-989593.patch b/ghc-64bit-bigendian-rts-hang-989593.patch new file mode 100644 index 0000000..279e666 --- /dev/null +++ b/ghc-64bit-bigendian-rts-hang-989593.patch @@ -0,0 +1,11 @@ +--- a/rts/STM.c ++++ b/rts/STM.c +@@ -927,7 +927,7 @@ void stmPreGCHook (Capability *cap) { + static volatile StgInt64 max_commits = 0; + + #if defined(THREADED_RTS) +-static volatile StgBool token_locked = FALSE; ++static volatile StgWord token_locked = FALSE; + + static void getTokenBatch(Capability *cap) { + while (cas((void *)&token_locked, FALSE, TRUE) == TRUE) { /* nothing */ } diff --git a/ghc-cabal-unversion-docdir.patch b/ghc-cabal-unversion-docdir.patch new file mode 100644 index 0000000..0aefeb5 --- /dev/null +++ b/ghc-cabal-unversion-docdir.patch @@ -0,0 +1,13 @@ +--- ghc-7.6.3/utils/ghc-cabal/Main.hs~ 2013-04-19 06:22:47.000000000 +0900 ++++ ghc-7.6.3/utils/ghc-cabal/Main.hs 2013-10-29 12:35:18.916340631 +0900 +@@ -180,8 +180,8 @@ + libsubdir = toPathTemplate "$pkgid", + docdir = toPathTemplate $ + if relocatableBuild +- then "$topdir/../doc/html/libraries/$pkgid" +- else (myDocdir "$pkgid"), ++ then "$topdir/../doc/html/libraries/$pkg" ++ else (myDocdir "$pkg"), + htmldir = toPathTemplate "$docdir" + } + progs = withPrograms lbi diff --git a/ghc.spec b/ghc.spec index dc2e8f5..ca969df 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,10 +2,11 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%{?ghc_bootstrap} -#%%global without_testsuite 1 -#%%global without_haddock 1 +%global ghc_bootstrapping 1 +%{?ghc_bootstrap} +%global without_testsuite 1 +# uncomment to generate haddocks +#%%undefine without_haddock # To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 @@ -29,7 +30,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 18%{?dist} +Release: 19%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -54,6 +55,10 @@ Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch Patch13: ghc-llvmCodeGen-empty-array.patch # stop warnings about unsupported version of llvm Patch14: ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch +# fix hang on ppc64 and s390x +Patch15: ghc-64bit-bigendian-rts-hang-989593.patch +# unversion library html docdirs +Patch16: ghc-cabal-unversion-docdir.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -133,8 +138,9 @@ Requires: llvm >= 3.0 %description compiler The package contains the GHC compiler, tools and utilities. -The ghc libraries are provided by ghc-devel. -To install all of ghc, install the ghc base package. +The ghc libraries are provided by ghc-libraries. +To install all of ghc (including the ghc library), +install the main ghc package. %if %{undefined without_haddock} %package doc-index @@ -234,6 +240,21 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch14 -p1 -b .orig %endif +# #FIXME: apply to all archs from next version bootstrap +%ifarch ppc64 s390x +%patch15 -p1 -b .orig +%endif + +%patch16 -p1 -b .orig + +%global gen_contents_index gen_contents_index.orig +%if %{undefined without_haddock} +if [ ! -f "libraries/%{gen_contents_index}" ]; then + echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!" + exit 1 +fi +%endif + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms @@ -253,6 +274,8 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif +# for verbose build output +#GhcStage1HcOpts=-v4 EOF export CFLAGS="${CFLAGS:-%optflags}" @@ -264,7 +287,8 @@ export CFLAGS="${CFLAGS:-%optflags}" --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --with-gcc=%{_bindir}/gcc -make %{?_smp_mflags} +# utf8 is needed when building with verbose output +LANG=en_US.utf8 make %{?_smp_mflags} %install @@ -320,6 +344,11 @@ mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p %{buildroot}%{_localstatedir}/lib/ghc install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index + +# generate initial lib doc index +cd libraries +sh %{gen_contents_index} --intree --verbose +cd .. %endif @@ -446,6 +475,14 @@ fi %changelog +* Tue Oct 29 2013 Jens Petersen - 7.6.3-19 +- fix rts hang on 64bit bigendian archs (patch by Gustavo Luiz Duarte, #989593) +- generate and ship library doc index for ghc bundled libraries +- build with utf8 encoding (needed for verbose ghc output + and makes better sense anyway) +- change ghc-cabal to make library html docdirs unversioned +- bootstrap build + * Sat Jul 27 2013 Jóhann B. Guðmundsson - 7.6.3-18 - ghc-doc-index requires crontabs and mark cron file config noreplace (http://fedoraproject.org/wiki/Packaging:CronFiles) From 1cb04aa6afa8110af3e365f967fde0e24e200c33 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 30 Oct 2013 00:21:19 +0900 Subject: [PATCH 361/530] enable debuginfo production build --- ghc.spec | 23 +++++++++++------------ 1 file changed, 11 insertions(+), 12 deletions(-) diff --git a/ghc.spec b/ghc.spec index ca969df..5dae9fc 100644 --- a/ghc.spec +++ b/ghc.spec @@ -2,23 +2,18 @@ # (disabled for other archs in ghc-rpm-macros) # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%{?ghc_bootstrap} -%global without_testsuite 1 -# uncomment to generate haddocks -#%%undefine without_haddock - -# To do a test build instead with shared libs, uncomment the following: #%%global ghc_bootstrapping 1 -#%%{?ghc_test} #%%global without_testsuite 1 +# either: +#%%{?ghc_bootstrap} +# or for shared libs: +#%%{?ghc_test} +# uncomment to generate haddocks for bootstrap +#%%undefine without_haddock # unregisterized archs %global unregisterised_archs ppc64 s390 s390x -# ghc does not output dwarf format so debuginfo is not useful -%global debug_package %{nil} - %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport @@ -30,7 +25,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 19%{?dist} +Release: 20%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -475,6 +470,10 @@ fi %changelog +* Wed Oct 30 2013 Jens Petersen - 7.6.3-20 +- enable debuginfo for C code bits (#989593) +- back to production build + * Tue Oct 29 2013 Jens Petersen - 7.6.3-19 - fix rts hang on 64bit bigendian archs (patch by Gustavo Luiz Duarte, #989593) - generate and ship library doc index for ghc bundled libraries From 0b7166425482ab31691a43042658f26f5f99acb4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 22 Dec 2013 21:56:20 +0900 Subject: [PATCH 362/530] document RTS debugging build option --- ghc.spec | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5dae9fc..7e8aa41 100644 --- a/ghc.spec +++ b/ghc.spec @@ -4,11 +4,11 @@ # To bootstrap build a new version of ghc, uncomment the following: #%%global ghc_bootstrapping 1 #%%global without_testsuite 1 -# either: +### either: #%%{?ghc_bootstrap} -# or for shared libs: +### or for shared libs: #%%{?ghc_test} -# uncomment to generate haddocks for bootstrap +### uncomment to generate haddocks for bootstrap #%%undefine without_haddock # unregisterized archs @@ -269,8 +269,11 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif -# for verbose build output +## for verbose build output #GhcStage1HcOpts=-v4 +## enable RTS debugging: +## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) +#EXTRA_HC_OPTS=-debug EOF export CFLAGS="${CFLAGS:-%optflags}" From 7f1dc7792cd8c897a884de465982a105859de328 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 29 Jan 2014 11:26:21 +0900 Subject: [PATCH 363/530] fix segfault on i686 when using ffi double-mapping for selinux (#907515) - originally noticed with gtk2hs - see http://hackage.haskell.org/trac/ghc/ticket/7629 - thanks Garrett Mitchener for patch committed upstream --- ghc-7.6.3-rts-Adjustor-32bit-segfault.patch | 11 +++++++++++ ghc.spec | 11 ++++++++++- 2 files changed, 21 insertions(+), 1 deletion(-) create mode 100644 ghc-7.6.3-rts-Adjustor-32bit-segfault.patch diff --git a/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch b/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch new file mode 100644 index 0000000..ca608e7 --- /dev/null +++ b/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch @@ -0,0 +1,11 @@ +Index: rts/Adjustor.c +=================================================================== +--- rts/Adjustor.c (revision c2870706b29c24ac86ae2a9e2359dd1e4af71ac8) ++++ rts/Adjustor.c (revision 27cf625ab871f34434d9fe86cecf85a31f73f0e5) +@@ -390,5 +390,5 @@ + + adjustorStub->call[0] = 0xe8; +- *(long*)&adjustorStub->call[1] = ((char*)&adjustorCode) - ((char*)adjustorStub + 5); ++ *(long*)&adjustorStub->call[1] = ((char*)&adjustorCode) - ((char*)code + 5); + adjustorStub->hptr = hptr; + adjustorStub->wptr = wptr; diff --git a/ghc.spec b/ghc.spec index 7e8aa41..20cf82e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -25,7 +25,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 20%{?dist} +Release: 21%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -54,6 +54,8 @@ Patch14: ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch Patch15: ghc-64bit-bigendian-rts-hang-989593.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch +# fix libffi segfaults on 32bit +Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -242,6 +244,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch16 -p1 -b .orig +%patch17 -p0 -b .orig + %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} if [ ! -f "libraries/%{gen_contents_index}" ]; then @@ -473,6 +477,11 @@ fi %changelog +* Wed Jan 29 2014 Jens Petersen - 7.6.3-21 +- fix segfault on i686 when using ffi double-mapping for selinux (#907515) + see http://hackage.haskell.org/trac/ghc/ticket/7629 + (thanks Garrett Mitchener for patch committed upstream) + * Wed Oct 30 2013 Jens Petersen - 7.6.3-20 - enable debuginfo for C code bits (#989593) - back to production build From fe81a51aee522593a875aa31de0338317ae92812 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 29 Jan 2014 13:01:43 +0900 Subject: [PATCH 364/530] comment on a couple of patches upstream --- ghc.spec | 5 ++--- 1 file changed, 2 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 20cf82e..a966b29 100644 --- a/ghc.spec +++ b/ghc.spec @@ -50,11 +50,11 @@ Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch Patch13: ghc-llvmCodeGen-empty-array.patch # stop warnings about unsupported version of llvm Patch14: ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch -# fix hang on ppc64 and s390x +# fix hang on ppc64 and s390x (upstream in 7.8) Patch15: ghc-64bit-bigendian-rts-hang-989593.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch -# fix libffi segfaults on 32bit +# fix libffi segfaults on 32bit (upstream in 7.8) Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch # fedora ghc has been bootstrapped on @@ -237,7 +237,6 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch14 -p1 -b .orig %endif -# #FIXME: apply to all archs from next version bootstrap %ifarch ppc64 s390x %patch15 -p1 -b .orig %endif From 047624e51819b1ad142495ef55d428fccfab7c68 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 30 Jan 2014 14:02:36 +0900 Subject: [PATCH 365/530] do not link executables with executable stack flag set (#973512) - upstream patch by Edward Z Yang - http://ghc.haskell.org/trac/ghc/ticket/703 - note this changes the ABI hash of the ghc library --- ...executable-stack-for-the-linker-note.patch | 37 +++++++++++++++++++ ghc.spec | 11 +++++- 2 files changed, 47 insertions(+), 1 deletion(-) create mode 100644 ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch diff --git a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch new file mode 100644 index 0000000..63583af --- /dev/null +++ b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch @@ -0,0 +1,37 @@ +From 08a38628f29df63ac842f4d083efb414f42d7bff Mon Sep 17 00:00:00 2001 +From: "Edward Z. Yang" +Date: Tue, 9 Jul 2013 00:01:43 -0700 +Subject: [PATCH] Disable executable stack for the linker note, fixing #703 + (again) + +Signed-off-by: Edward Z. Yang +--- + compiler/main/DriverPipeline.hs | 12 +++++++++++- + 1 file changed, 11 insertions(+), 1 deletion(-) + +diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs +index 67377e6..26425ae 100644 +--- a/compiler/main/DriverPipeline.hs ++++ b/compiler/main/DriverPipeline.hs +@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do + text elfSectionNote, + text "\n", + +- text "\t.ascii \"", info', text "\"\n" ] ++ text "\t.ascii \"", info', text "\"\n", ++ ++ -- ALL generated assembly must have this section to disable ++ -- executable stacks. See also ++ -- compiler/nativeGen/AsmCodeGen.lhs for another instance ++ -- where we need to do this. ++ (if platformHasGnuNonexecStack (targetPlatform dflags) ++ then text ".section .note.GNU-stack,\"\",@progbits\n" ++ else empty) ++ ++ ] + where + info' = text $ escape info + +-- +1.8.1.2 + diff --git a/ghc.spec b/ghc.spec index a966b29..1fce3dd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -25,7 +25,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 21%{?dist} +Release: 22%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -56,6 +56,8 @@ Patch15: ghc-64bit-bigendian-rts-hang-989593.patch Patch16: ghc-cabal-unversion-docdir.patch # fix libffi segfaults on 32bit (upstream in 7.8) Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch +# add .note.GNU-stack to assembly output to avoid execstack (#973512) +Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -245,6 +247,8 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch17 -p0 -b .orig +%patch18 -p1 -b .orig + %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} if [ ! -f "libraries/%{gen_contents_index}" ]; then @@ -476,6 +480,11 @@ fi %changelog +* Thu Jan 30 2014 Jens Petersen - 7.6.3-22 +- do not set executable stack on executables (#973512) + (upstream patch by Edward Z Yang) +- note this patch changes the ABI hash of the ghc library + * Wed Jan 29 2014 Jens Petersen - 7.6.3-21 - fix segfault on i686 when using ffi double-mapping for selinux (#907515) see http://hackage.haskell.org/trac/ghc/ticket/7629 From 1ca269a8ceebd0b0d5ff286169963f1633b8b4c4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 30 May 2014 12:11:35 +0900 Subject: [PATCH 366/530] add ppc64le support with patch from Debian (Fedora bootstrap by jcapik) add *_ver macros variables for library versions --- ghc-ppc64el.patch | 41 ++++++++++++++++ ghc.spec | 118 ++++++++++++++++++++++++++++++++-------------- 2 files changed, 123 insertions(+), 36 deletions(-) create mode 100644 ghc-ppc64el.patch diff --git a/ghc-ppc64el.patch b/ghc-ppc64el.patch new file mode 100644 index 0000000..9841054 --- /dev/null +++ b/ghc-ppc64el.patch @@ -0,0 +1,41 @@ +Description: Add ppc64el support +Author: Colin Watson +Bug: https://ghc.haskell.org/trac/ghc/ticket/8965 +Last-Update: 2014-04-12 + +Index: b/aclocal.m4 +=================================================================== +--- a/aclocal.m4 ++++ b/aclocal.m4 +@@ -173,7 +173,7 @@ + GET_ARM_ISA() + test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" + ;; +- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) ++ alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) + test -z "[$]2" || eval "[$]2=ArchUnknown" + ;; + *) +@@ -1868,6 +1868,9 @@ + mips*) + $2="mips" + ;; ++ powerpc64le*) ++ $2="powerpc64le" ++ ;; + powerpc64*) + $2="powerpc64" + ;; +Index: b/includes/Stg.h +=================================================================== +--- a/includes/Stg.h ++++ b/includes/Stg.h +@@ -213,7 +213,7 @@ + #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) + #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) + #define FN_(f) StgFunPtr f(void) +-#define EF_(f) extern StgFunPtr f(void) ++#define EF_(f) extern StgFunPtr f() + + /* ----------------------------------------------------------------------------- + Tail calls diff --git a/ghc.spec b/ghc.spec index 1fce3dd..97167d2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -12,11 +12,35 @@ #%%undefine without_haddock # unregisterized archs -%global unregisterised_archs ppc64 s390 s390x +%global unregisterised_archs ppc64 s390 s390x ppc64le %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport +%global Cabal_ver 1.16.0 +%global array_ver 0.4.0.1 +%global base_ver 4.6.0.1 +%global bin_package_db_ver 0.0.0.0 +%global binary_ver 0.5.1.1 +%global bytestring_ver 0.10.0.2 +%global containers_ver 0.5.0.0 +%global deepseq_ver 1.3.0.1 +%global directory_ver 1.2.0.1 +%global filepath_ver 1.3.0.1 +%global ghc_prim_ver 0.3.0.0 +%global haskell2010_ver 1.1.1.0 +%global haskell98_ver 2.0.0.2 +%global hoopl_ver 3.9.0.0 +%global hpc_ver 0.6.0.0 +%global integer_gmp_ver 0.5.0.0 +%global old_locale_ver 1.0.0.5 +%global old_time_ver 1.1.0.1 +%global pretty_ver 1.1.1.0 +%global process_ver 1.1.0.2 +%global template_haskell_ver 2.8.0.0 +%global time_ver 1.4.0.1 +%global unix_ver 2.6.0.1 + Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems @@ -57,7 +81,11 @@ Patch16: ghc-cabal-unversion-docdir.patch # fix libffi segfaults on 32bit (upstream in 7.8) Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch # add .note.GNU-stack to assembly output to avoid execstack (#973512) -Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch +# (disabled for now since it changes libghc ABI and fix only works for i686) +#Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch +# changes for ppc64le committed upstream for 7.8.3 +# (https://ghc.haskell.org/trac/ghc/ticket/8965) +Patch19: ghc-ppc64el.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -73,7 +101,11 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif +%if 0%{?fedora} >= 20 BuildRequires: ghc-rpm-macros-extra +%else +BuildRequires: ghc-rpm-macros +%endif BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -84,15 +116,18 @@ BuildRequires: gmp-devel BuildRequires: libffi-devel # for internal terminfo BuildRequires: ncurses-devel -%if %{undefined without_manual} +# for manpage and docs BuildRequires: libxslt, docbook-style-xsl -%endif %if %{undefined without_testsuite} BuildRequires: python %endif %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif +%ifarch ppc64le +# for patch19 +BuildRequires: autoconf +%endif Requires: ghc-compiler = %{version}-%{release} %if %{undefined without_haddock} Requires: ghc-doc-index = %{version}-%{release} @@ -164,32 +199,32 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_lib_subpackage Cabal 1.16.0 -%ghc_lib_subpackage -l %BSDHaskellReport array 0.4.0.1 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base 4.6.0.1 -%ghc_lib_subpackage binary 0.5.1.1 -%ghc_lib_subpackage bytestring 0.10.0.2 -%ghc_lib_subpackage -l %BSDHaskellReport containers 0.5.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport deepseq 1.3.0.1 -%ghc_lib_subpackage -l %BSDHaskellReport directory 1.2.0.1 -%ghc_lib_subpackage filepath 1.3.0.1 +%ghc_lib_subpackage Cabal %{Cabal_ver} +%ghc_lib_subpackage -l %BSDHaskellReport array %{array_ver} +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base %{base_ver} +%ghc_lib_subpackage binary %{binary_ver} +%ghc_lib_subpackage bytestring %{bytestring_ver} +%ghc_lib_subpackage -l %BSDHaskellReport containers %{containers_ver} +%ghc_lib_subpackage -l %BSDHaskellReport deepseq %{deepseq_ver} +%ghc_lib_subpackage -l %BSDHaskellReport directory %{directory_ver} +%ghc_lib_subpackage filepath %{filepath_ver} %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -l HaskellReport haskell2010 1.1.1.0 -%ghc_lib_subpackage -l HaskellReport haskell98 2.0.0.2 -%ghc_lib_subpackage hoopl 3.9.0.0 -%ghc_lib_subpackage hpc 0.6.0.0 -%ghc_lib_subpackage -l %BSDHaskellReport old-locale 1.0.0.5 -%ghc_lib_subpackage -l %BSDHaskellReport old-time 1.1.0.1 -%ghc_lib_subpackage pretty 1.1.1.0 +%ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver} +%ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver} +%ghc_lib_subpackage hoopl %{hoopl_ver} +%ghc_lib_subpackage hpc %{hpc_ver} +%ghc_lib_subpackage -l %BSDHaskellReport old-locale %{old_locale_ver} +%ghc_lib_subpackage -l %BSDHaskellReport old-time %{old_time_ver} +%ghc_lib_subpackage pretty %{pretty_ver} %define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 -%ghc_lib_subpackage -l %BSDHaskellReport process 1.1.0.2 +%ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage template-haskell 2.8.0.0 -%ghc_lib_subpackage time 1.4.0.1 -%ghc_lib_subpackage unix 2.6.0.1 +%ghc_lib_subpackage template-haskell %{template_haskell_ver} +%ghc_lib_subpackage time %{time_ver} +%ghc_lib_subpackage unix %{unix_ver} %endif %global version %{ghc_version_override} @@ -247,7 +282,11 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch17 -p0 -b .orig -%patch18 -p1 -b .orig +#%%patch18 -p1 -b .orig + +%ifarch ppc64le +%patch19 -p1 -b .orig +%endif %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -284,7 +323,14 @@ BUILD_DOCBOOK_HTML = NO EOF export CFLAGS="${CFLAGS:-%optflags}" -# use --with-gcc=%{_bindir}/gcc when bootstrapping to avoid ccache hardcoding problem +# note %%configure induces cross-build due to different target/host/build platform names +# --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping +%ifarch ppc64le +for i in $(find . -name config.guess -o -name config.sub) ; do + [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i +done +autoreconf +%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -309,10 +355,10 @@ done # ghc-base should own ghclibdir echo "%dir %{ghclibdir}" >> ghc-base.files -%ghc_gen_filelists bin-package-db 0.0.0.0 +%ghc_gen_filelists bin-package-db %{bin_package_db_ver} %ghc_gen_filelists ghc %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.3.0.0 -%ghc_gen_filelists integer-gmp 0.5.0.0 +%ghc_gen_filelists ghc-prim %{ghc_prim_ver} +%ghc_gen_filelists integer-gmp %{integer_gmp_ver} %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ @@ -359,22 +405,23 @@ cd .. %check # stolen from ghc6/debian/rules: +GHC=inplace/bin/ghc-stage2 # Do some very simple tests that the compiler actually works rm -rf testghc mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs -inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo +$GHC testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] # doesn't seem to work inplace: #[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs -inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -O2 +$GHC testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* %if %{undefined ghc_without_shared} echo 'main = putStrLn "Foo"' > testghc/foo.hs -inplace/bin/ghc-stage2 testghc/foo.hs -o testghc/foo -dynamic +$GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* %endif @@ -480,10 +527,9 @@ fi %changelog -* Thu Jan 30 2014 Jens Petersen - 7.6.3-22 -- do not set executable stack on executables (#973512) - (upstream patch by Edward Z Yang) -- note this patch changes the ABI hash of the ghc library +* Fri May 30 2014 Jens Petersen - 7.6.3-22 +- add ppc64le support patch from Debian by Colin Watson + (thanks to Jaromir Capik for Fedora ppc64le bootstrap) * Wed Jan 29 2014 Jens Petersen - 7.6.3-21 - fix segfault on i686 when using ffi double-mapping for selinux (#907515) From 61e47f8bc2915a474ca54b664ec808a55ffee4fe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 30 May 2014 21:44:41 +0900 Subject: [PATCH 367/530] bump release --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 97167d2..6db1b53 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 22%{?dist} +Release: 23%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -527,6 +527,9 @@ fi %changelog +* Fri May 30 2014 Jens Petersen - 7.6.3-23 +- bump release + * Fri May 30 2014 Jens Petersen - 7.6.3-22 - add ppc64le support patch from Debian by Colin Watson (thanks to Jaromir Capik for Fedora ppc64le bootstrap) From 27b5c4e337816324c79ffa84aa467025b787de63 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 6 Jun 2014 13:22:58 +0900 Subject: [PATCH 368/530] add aarch64; silence glibc _BSD_SOURCE warnings on unregisterized archs --- .gitignore | 1 + ghc-arm64.patch | 188 ++++++++++++++++++++++++++++++++ ghc-glibc-2.20_BSD_SOURCE.patch | 11 ++ ghc.spec | 30 +++-- 4 files changed, 222 insertions(+), 8 deletions(-) create mode 100644 ghc-arm64.patch create mode 100644 ghc-glibc-2.20_BSD_SOURCE.patch diff --git a/.gitignore b/.gitignore index 9da11de..8654e4f 100644 --- a/.gitignore +++ b/.gitignore @@ -11,3 +11,4 @@ testsuite-6.12.3.tar.bz2 /ghc-7.4.2-testsuite.tar.bz2 /ghc-7.6.3-src.tar.bz2 /ghc-7.6.3-testsuite.tar.bz2 +/ghc-7.6.3/ diff --git a/ghc-arm64.patch b/ghc-arm64.patch new file mode 100644 index 0000000..06a7019 --- /dev/null +++ b/ghc-arm64.patch @@ -0,0 +1,188 @@ +Description: Add arm64 support +Author: Karel Gardas +Author: Colin Watson +Bug: https://ghc.haskell.org/trac/ghc/ticket/7942 +Last-Update: 2014-04-04 + +Index: b/aclocal.m4 +=================================================================== +--- a/aclocal.m4 ++++ b/aclocal.m4 +@@ -173,7 +173,7 @@ + GET_ARM_ISA() + test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" + ;; +- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) ++ aarch64|alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + test -z "[$]2" || eval "[$]2=ArchUnknown" + ;; + *) +@@ -1835,6 +1835,9 @@ + # converts cpu from gnu to ghc naming, and assigns the result to $target_var + AC_DEFUN([GHC_CONVERT_CPU],[ + case "$1" in ++ aarch64*) ++ $2="aarch64" ++ ;; + alpha*) + $2="alpha" + ;; +Index: b/includes/stg/MachRegs.h +=================================================================== +--- a/includes/stg/MachRegs.h ++++ b/includes/stg/MachRegs.h +@@ -43,6 +43,7 @@ + #define powerpc_REGS (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) + #define sparc_REGS sparc_TARGET_ARCH + #define arm_REGS arm_TARGET_ARCH ++#define aarch64_REGS aarch64_TARGET_ARCH + #define darwin_REGS darwin_TARGET_OS + #else + #define i386_REGS i386_HOST_ARCH +@@ -50,6 +51,7 @@ + #define powerpc_REGS (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH) + #define sparc_REGS sparc_HOST_ARCH + #define arm_REGS arm_HOST_ARCH ++#define aarch64_REGS aarch64_HOST_ARCH + #define darwin_REGS darwin_HOST_OS + #endif + +@@ -461,6 +463,63 @@ + + #endif /* arm */ + ++/* ----------------------------------------------------------------------------- ++ The ARMv8/AArch64 ABI register mapping ++ ++ The AArch64 provides 31 64-bit general purpose registers ++ and 32 128-bit SIMD/floating point registers. ++ ++ General purpose registers (see Chapter 5.1.1 in ARM IHI 0055B) ++ ++ Register | Special | Role in the procedure call standard ++ ---------+---------+------------------------------------ ++ SP | | The Stack Pointer ++ r30 | LR | The Link Register ++ r29 | FP | The Frame Pointer ++ r19-r28 | | Callee-saved registers ++ r18 | | The Platform Register, if needed; ++ | | or temporary register ++ r17 | IP1 | The second intra-procedure-call temporary register ++ r16 | IP0 | The first intra-procedure-call scratch register ++ r9-r15 | | Temporary registers ++ r8 | | Indirect result location register ++ r0-r7 | | Parameter/result registers ++ ++ ++ FPU/SIMD registers ++ ++ s/d/q/v0-v7 Argument / result/ scratch registers ++ s/d/q/v8-v15 callee-saved registers (must be preserved across subrutine calls, ++ but only bottom 64-bit value needs to be preserved) ++ s/d/q/v16-v31 temporary registers ++ ++ ----------------------------------------------------------------------------- */ ++ ++#if aarch64_REGS ++ ++#define REG(x) __asm__(#x) ++ ++#define REG_Base r19 ++#define REG_Sp r20 ++#define REG_Hp r21 ++#define REG_R1 r22 ++#define REG_R2 r23 ++#define REG_R3 r24 ++#define REG_R4 r25 ++#define REG_R5 r26 ++#define REG_R6 r27 ++#define REG_SpLim r28 ++ ++#define REG_F1 s8 ++#define REG_F2 s9 ++#define REG_F3 s10 ++#define REG_F4 s11 ++ ++#define REG_D1 d12 ++#define REG_D2 d13 ++ ++#endif /* aarch64 */ ++ + #endif /* NO_REGS */ + + /* ----------------------------------------------------------------------------- +Index: b/rts/StgCRun.c +=================================================================== +--- a/rts/StgCRun.c ++++ b/rts/StgCRun.c +@@ -725,4 +725,70 @@ + } + #endif + ++#ifdef aarch64_HOST_ARCH ++ ++StgRegTable * ++StgRun(StgFunPtr f, StgRegTable *basereg) { ++ StgRegTable * r; ++ __asm__ volatile ( ++ /* ++ * save callee-saves registers on behalf of the STG code. ++ */ ++ "stp x19, x20, [sp, #-16]!\n\t" ++ "stp x21, x22, [sp, #-16]!\n\t" ++ "stp x23, x24, [sp, #-16]!\n\t" ++ "stp x25, x26, [sp, #-16]!\n\t" ++ "stp x27, x28, [sp, #-16]!\n\t" ++ "stp ip0, ip1, [sp, #-16]!\n\t" ++ "str lr, [sp, #-8]!\n\t" ++ ++ /* ++ * allocate some space for Stg machine's temporary storage. ++ * Note: RESERVER_C_STACK_BYTES has to be a round number here or ++ * the assembler can't assemble it. ++ */ ++ "str lr, [sp, %3]" ++ /* "sub sp, sp, %3\n\t" */ ++ /* ++ * Set BaseReg ++ */ ++ "mov x19, %2\n\t" ++ /* ++ * Jump to function argument. ++ */ ++ "bx %1\n\t" ++ ++ ".globl " STG_RETURN "\n\t" ++ ".type " STG_RETURN ", %%function\n" ++ STG_RETURN ":\n\t" ++ /* ++ * Free the space we allocated ++ */ ++ "ldr lr, [sp], %3\n\t" ++ /* "add sp, sp, %3\n\t" */ ++ /* ++ * Return the new register table, taking it from Stg's R1 (ARM64's R22). ++ */ ++ "mov %0, x22\n\t" ++ /* ++ * restore callee-saves registers. ++ */ ++ "ldr lr, [sp], #8\n\t" ++ "ldp ip0, ip1, [sp], #16\n\t" ++ "ldp x27, x28, [sp], #16\n\t" ++ "ldp x25, x26, [sp], #16\n\t" ++ "ldp x23, x24, [sp], #16\n\t" ++ "ldp x21, x22, [sp], #16\n\t" ++ "ldp x19, x20, [sp], #16\n\t" ++ ++ : "=r" (r) ++ : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) ++ : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", ++ "%ip0", "%ip1", "%lr" ++ ); ++ return r; ++} ++ ++#endif ++ + #endif /* !USE_MINIINTERPRETER */ diff --git a/ghc-glibc-2.20_BSD_SOURCE.patch b/ghc-glibc-2.20_BSD_SOURCE.patch new file mode 100644 index 0000000..6836cfb --- /dev/null +++ b/ghc-glibc-2.20_BSD_SOURCE.patch @@ -0,0 +1,11 @@ +--- ghc-7.6.3/includes/Stg.h~ 2013-04-19 06:22:46.000000000 +0900 ++++ ghc-7.6.3/includes/Stg.h 2014-06-06 13:01:40.881289598 +0900 +@@ -46,7 +46,7 @@ + + // We need _BSD_SOURCE so that math.h defines things like gamma + // on Linux +-# define _BSD_SOURCE ++# define _DEFAULT_SOURCE + #endif + + #if IN_STG_CODE == 0 || defined(llvm_CC_FLAVOR) diff --git a/ghc.spec b/ghc.spec index 6db1b53..7a10396 100644 --- a/ghc.spec +++ b/ghc.spec @@ -11,9 +11,6 @@ ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock -# unregisterized archs -%global unregisterised_archs ppc64 s390 s390x ppc64le - %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport @@ -49,7 +46,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 23%{?dist} +Release: 24%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -86,6 +83,10 @@ Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch # changes for ppc64le committed upstream for 7.8.3 # (https://ghc.haskell.org/trac/ghc/ticket/8965) Patch19: ghc-ppc64el.patch +# warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" +Patch20: ghc-glibc-2.20_BSD_SOURCE.patch +# Debian patch +Patch21: ghc-arm64.patch # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -124,8 +125,8 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif -%ifarch ppc64le -# for patch19 +%ifarch ppc64le aarch64 +# for patch19 and patch21 BuildRequires: autoconf %endif Requires: ghc-compiler = %{version}-%{release} @@ -288,6 +289,13 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch19 -p1 -b .orig %endif +%patch20 -p1 -b .orig + +%ifarch aarch64 +%patch21 -p1 -b .orig +%endif + + %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} if [ ! -f "libraries/%{gen_contents_index}" ]; then @@ -325,7 +333,7 @@ EOF export CFLAGS="${CFLAGS:-%optflags}" # note %%configure induces cross-build due to different target/host/build platform names # --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping -%ifarch ppc64le +%ifarch ppc64le aarch64 for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done @@ -474,7 +482,8 @@ fi %{_bindir}/runhaskell-ghc %{ghclibdir}/ghc %{ghclibdir}/ghc-pkg -%ifnarch %{unregisterised_archs} +# unknown ("unregisterized") archs +%ifnarch ppc64 s390 s390x ppc64le aarch64 %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt @@ -527,6 +536,11 @@ fi %changelog +* Fri Jun 6 2014 Jens Petersen - 7.6.3-24 +- add aarch64 with Debian patch by Karel Gardas and Colin Watson +- patch Stg.h to define _DEFAULT_SOURCE instead of _BSD_SOURCE to quieten + glibc 2.20 warnings (see #1067110) + * Fri May 30 2014 Jens Petersen - 7.6.3-23 - bump release From 557b1571ca035e9623e339c94705ed123e07afb6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 9 Jun 2014 14:46:34 +0900 Subject: [PATCH 369/530] move library versions to after patches for easier reading of top of ghc.spec --- ghc.spec | 48 ++++++++++++++++++++++++------------------------ 1 file changed, 24 insertions(+), 24 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7a10396..b2eb2c7 100644 --- a/ghc.spec +++ b/ghc.spec @@ -14,30 +14,6 @@ %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport -%global Cabal_ver 1.16.0 -%global array_ver 0.4.0.1 -%global base_ver 4.6.0.1 -%global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.5.1.1 -%global bytestring_ver 0.10.0.2 -%global containers_ver 0.5.0.0 -%global deepseq_ver 1.3.0.1 -%global directory_ver 1.2.0.1 -%global filepath_ver 1.3.0.1 -%global ghc_prim_ver 0.3.0.0 -%global haskell2010_ver 1.1.1.0 -%global haskell98_ver 2.0.0.2 -%global hoopl_ver 3.9.0.0 -%global hpc_ver 0.6.0.0 -%global integer_gmp_ver 0.5.0.0 -%global old_locale_ver 1.0.0.5 -%global old_time_ver 1.1.0.1 -%global pretty_ver 1.1.1.0 -%global process_ver 1.1.0.2 -%global template_haskell_ver 2.8.0.0 -%global time_ver 1.4.0.1 -%global unix_ver 2.6.0.1 - Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems @@ -88,6 +64,30 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch +%global Cabal_ver 1.16.0 +%global array_ver 0.4.0.1 +%global base_ver 4.6.0.1 +%global bin_package_db_ver 0.0.0.0 +%global binary_ver 0.5.1.1 +%global bytestring_ver 0.10.0.2 +%global containers_ver 0.5.0.0 +%global deepseq_ver 1.3.0.1 +%global directory_ver 1.2.0.1 +%global filepath_ver 1.3.0.1 +%global ghc_prim_ver 0.3.0.0 +%global haskell2010_ver 1.1.1.0 +%global haskell98_ver 2.0.0.2 +%global hoopl_ver 3.9.0.0 +%global hpc_ver 0.6.0.0 +%global integer_gmp_ver 0.5.0.0 +%global old_locale_ver 1.0.0.5 +%global old_time_ver 1.1.0.1 +%global pretty_ver 1.1.1.0 +%global process_ver 1.1.0.2 +%global template_haskell_ver 2.8.0.0 +%global time_ver 1.4.0.1 +%global unix_ver 2.6.0.1 + # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros From 54a5ce4f5326e51d6482a5e33833dbdb2b542b97 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 9 Jun 2014 17:04:51 +0900 Subject: [PATCH 370/530] update ghc-glibc-2.20_BSD_SOURCE.patch to version submitted upstream --- ghc-glibc-2.20_BSD_SOURCE.patch | 25 ++++++++++++++++++++----- 1 file changed, 20 insertions(+), 5 deletions(-) diff --git a/ghc-glibc-2.20_BSD_SOURCE.patch b/ghc-glibc-2.20_BSD_SOURCE.patch index 6836cfb..0b9d94a 100644 --- a/ghc-glibc-2.20_BSD_SOURCE.patch +++ b/ghc-glibc-2.20_BSD_SOURCE.patch @@ -1,11 +1,26 @@ ---- ghc-7.6.3/includes/Stg.h~ 2013-04-19 06:22:46.000000000 +0900 -+++ ghc-7.6.3/includes/Stg.h 2014-06-06 13:01:40.881289598 +0900 -@@ -46,7 +46,7 @@ - +From 7d738547049e686be4d90a19dcb9520418d5f72d Mon Sep 17 00:00:00 2001 +From: Jens Petersen +Date: Mon, 9 Jun 2014 15:48:41 +0900 +Subject: [PATCH] define _DEFAULT_SOURCE in Stg.h to avoid warnings from glibc + 2.20 (#9185) + +--- + includes/Stg.h | 2 ++ + 1 file changed, 2 insertions(+) + +diff --git a/includes/Stg.h b/includes/Stg.h +index 1707c9b..fbcf643 100644 +--- a/includes/Stg.h ++++ b/includes/Stg.h +@@ -47,6 +47,8 @@ // We need _BSD_SOURCE so that math.h defines things like gamma // on Linux --# define _BSD_SOURCE + # define _BSD_SOURCE ++// glibc 2.20 deprecates _BSD_SOURCE in favour of _DEFAULT_SOURCE +# define _DEFAULT_SOURCE #endif #if IN_STG_CODE == 0 || defined(llvm_CC_FLAVOR) +-- +1.9.3 + From 38493537b2f40192e814a6600bd80ff28fa982e1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 25 Jul 2014 20:23:17 +0900 Subject: [PATCH 371/530] disable NEON on arm; only unversion docdir on f21+; hide llvm-3.4 warnings on arm --- ...6.3-LlvmCodeGen-llvm-version-warning.patch | 2 +- ghc-7.6.3-armv7-VFPv3D16--NEON.patch | 11 ++++++++++ ghc.spec | 22 ++++++++++++++++--- 3 files changed, 31 insertions(+), 4 deletions(-) rename ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch => ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch (93%) create mode 100644 ghc-7.6.3-armv7-VFPv3D16--NEON.patch diff --git a/ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch b/ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch similarity index 93% rename from ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch rename to ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch index d48abd4..ef274e6 100644 --- a/ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch +++ b/ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch @@ -5,7 +5,7 @@ maxSupportLlvmVersion :: LlvmVersion -maxSupportLlvmVersion = 31 -+maxSupportLlvmVersion = 33 ++maxSupportLlvmVersion = 34 -- ---------------------------------------------------------------------------- -- * Environment Handling diff --git a/ghc-7.6.3-armv7-VFPv3D16--NEON.patch b/ghc-7.6.3-armv7-VFPv3D16--NEON.patch new file mode 100644 index 0000000..6412ff5 --- /dev/null +++ b/ghc-7.6.3-armv7-VFPv3D16--NEON.patch @@ -0,0 +1,11 @@ +--- ghc-7.6.3/aclocal.m4~ 2013-04-19 06:22:46.000000000 +0900 ++++ ghc-7.6.3/aclocal.m4 2014-07-15 18:22:12.308929288 +0900 +@@ -349,7 +349,7 @@ + ], + [changequote(, )dnl + ARM_ISA=ARMv7 +- ARM_ISA_EXT="[VFPv3,NEON]" ++ ARM_ISA_EXT="[VFPv3D16]" + changequote([, ])dnl + ]) + ]) diff --git a/ghc.spec b/ghc.spec index b2eb2c7..56d7995 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 24%{?dist} +Release: 25%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -46,7 +46,7 @@ Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch # fix compilation with llvm-3.3 Patch13: ghc-llvmCodeGen-empty-array.patch # stop warnings about unsupported version of llvm -Patch14: ghc-7.6.3-LlvmCodeGen-no-3.3-warning.patch +Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # fix hang on ppc64 and s390x (upstream in 7.8) Patch15: ghc-64bit-bigendian-rts-hang-989593.patch # unversion library html docdirs @@ -63,6 +63,7 @@ Patch19: ghc-ppc64el.patch Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch +Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch %global Cabal_ver 1.16.0 %global array_ver 0.4.0.1 @@ -129,6 +130,10 @@ BuildRequires: llvm >= 3.0 # for patch19 and patch21 BuildRequires: autoconf %endif +%ifarch armv7hl +# patch22 +BuildRequires: autoconf, automake +%endif Requires: ghc-compiler = %{version}-%{release} %if %{undefined without_haddock} Requires: ghc-doc-index = %{version}-%{release} @@ -279,7 +284,9 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch15 -p1 -b .orig %endif +%if 0%{?fedora} >= 21 %patch16 -p1 -b .orig +%endif %patch17 -p0 -b .orig @@ -295,6 +302,10 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch21 -p1 -b .orig %endif +%ifarch armv7hl +%patch22 -p1 -b .orig +%endif + %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -333,7 +344,7 @@ EOF export CFLAGS="${CFLAGS:-%optflags}" # note %%configure induces cross-build due to different target/host/build platform names # --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping -%ifarch ppc64le aarch64 +%ifarch ppc64le aarch64 armv7hl for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done @@ -536,6 +547,11 @@ fi %changelog +* Tue Jul 15 2014 Jens Petersen - 7.6.3-25 +- configure ARM with VFPv3D16 and without NEON (#995419) +- only apply the Cabal unversion docdir patch to F21 and later +- hide llvm version warning on ARM now up to 3.4 + * Fri Jun 6 2014 Jens Petersen - 7.6.3-24 - add aarch64 with Debian patch by Karel Gardas and Colin Watson - patch Stg.h to define _DEFAULT_SOURCE instead of _BSD_SOURCE to quieten From d1dfce72b72416cc121c8b91749ec14b5a4e4a84 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 3 Aug 2014 23:54:24 +0900 Subject: [PATCH 372/530] major update to 7.8.3: bootstrap build --- .gitignore | 2 + ghc-cabal-unversion-docdir.patch | 26 ++--- ghc.spec | 174 +++++++++++++++---------------- sources | 4 +- 4 files changed, 104 insertions(+), 102 deletions(-) diff --git a/.gitignore b/.gitignore index 8654e4f..1975bde 100644 --- a/.gitignore +++ b/.gitignore @@ -12,3 +12,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.6.3-src.tar.bz2 /ghc-7.6.3-testsuite.tar.bz2 /ghc-7.6.3/ +/ghc-7.8.3-src.tar.xz +/ghc-7.8.3-testsuite.tar.xz diff --git a/ghc-cabal-unversion-docdir.patch b/ghc-cabal-unversion-docdir.patch index 0aefeb5..9d0b026 100644 --- a/ghc-cabal-unversion-docdir.patch +++ b/ghc-cabal-unversion-docdir.patch @@ -1,13 +1,13 @@ ---- ghc-7.6.3/utils/ghc-cabal/Main.hs~ 2013-04-19 06:22:47.000000000 +0900 -+++ ghc-7.6.3/utils/ghc-cabal/Main.hs 2013-10-29 12:35:18.916340631 +0900 -@@ -180,8 +180,8 @@ - libsubdir = toPathTemplate "$pkgid", - docdir = toPathTemplate $ - if relocatableBuild -- then "$topdir/../doc/html/libraries/$pkgid" -- else (myDocdir "$pkgid"), -+ then "$topdir/../doc/html/libraries/$pkg" -+ else (myDocdir "$pkg"), - htmldir = toPathTemplate "$docdir" - } - progs = withPrograms lbi +--- ghc-7.8/utils/ghc-cabal/Main.hs~ 2013-08-28 08:06:37.000000000 +0900 ++++ ghc-7.8/utils/ghc-cabal/Main.hs 2013-09-03 17:51:22.800653817 +0900 +@@ -251,8 +251,8 @@ + libsubdir = toPathTemplate "$pkgid", + docdir = toPathTemplate $ + if relocatableBuild +- then "$topdir/../doc/html/libraries/$pkgid" +- else (myDocdir "$pkgid"), ++ then "$topdir/../doc/html/libraries/$pkg" ++ else (myDocdir "$pkg"), + htmldir = toPathTemplate "$docdir" + } + diff --git a/ghc.spec b/ghc.spec index 56d7995..23e000f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,13 +1,12 @@ -# Shared haskell libraries are supported for x86* archs -# (disabled for other archs in ghc-rpm-macros) - # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%global without_testsuite 1 -### either: -#%%{?ghc_bootstrap} -### or for shared libs: -#%%{?ghc_test} +%global ghc_bootstrapping 1 +%global without_testsuite 1 +%global without_prof 1 +%if 0%{?fedora} >= 22 +%{?ghc_bootstrap} +%else +%{?ghc_test} +%endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock @@ -17,45 +16,31 @@ Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.6.3 +Version: 7.8.3 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 25%{?dist} +# xhtml moved from haskell-platform to ghc-7.8.3 +Release: 38%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport URL: http://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch -# fedora does not allow copy libraries -Patch4: ghc-use-system-libffi.patch -# fix dynamic linking of executables using Template Haskell -Patch9: Cabal-fix-dynamic-exec-for-TH.patch # add libffi include dir to ghc wrapper for archs using gcc/llc -Patch10: ghc-wrapper-libffi-include.patch -# disable building HS*.o libs for ghci -Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch -# fix compilation with llvm-3.3 -Patch13: ghc-llvmCodeGen-empty-array.patch +#Patch10: ghc-wrapper-libffi-include.patch # stop warnings about unsupported version of llvm Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch -# fix hang on ppc64 and s390x (upstream in 7.8) -Patch15: ghc-64bit-bigendian-rts-hang-989593.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch -# fix libffi segfaults on 32bit (upstream in 7.8) -Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch -# add .note.GNU-stack to assembly output to avoid execstack (#973512) -# (disabled for now since it changes libghc ABI and fix only works for i686) -#Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch # changes for ppc64le committed upstream for 7.8.3 # (https://ghc.haskell.org/trac/ghc/ticket/8965) Patch19: ghc-ppc64el.patch @@ -65,29 +50,34 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch Patch21: ghc-arm64.patch Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch -%global Cabal_ver 1.16.0 -%global array_ver 0.4.0.1 -%global base_ver 4.6.0.1 +%global Cabal_ver 1.18.1.3 +%global array_ver 0.5.0.0 +%global base_ver 4.7.0.1 %global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.5.1.1 -%global bytestring_ver 0.10.0.2 -%global containers_ver 0.5.0.0 -%global deepseq_ver 1.3.0.1 -%global directory_ver 1.2.0.1 -%global filepath_ver 1.3.0.1 -%global ghc_prim_ver 0.3.0.0 -%global haskell2010_ver 1.1.1.0 -%global haskell98_ver 2.0.0.2 -%global hoopl_ver 3.9.0.0 -%global hpc_ver 0.6.0.0 -%global integer_gmp_ver 0.5.0.0 -%global old_locale_ver 1.0.0.5 -%global old_time_ver 1.1.0.1 -%global pretty_ver 1.1.1.0 -%global process_ver 1.1.0.2 -%global template_haskell_ver 2.8.0.0 -%global time_ver 1.4.0.1 -%global unix_ver 2.6.0.1 +%global binary_ver 0.7.1.0 +%global bytestring_ver 0.10.4.0 +%global containers_ver 0.5.5.1 +%global deepseq_ver 1.3.0.2 +%global directory_ver 1.2.1.0 +%global filepath_ver 1.3.0.2 +%global ghc_prim_ver 0.3.1.0 +%global haskeline_ver 0.7.1.2 +%global haskell2010_ver 1.1.2.0 +%global haskell98_ver 2.0.0.3 +%global hoopl_ver 3.10.0.1 +%global hpc_ver 0.6.0.1 +%global integer_gmp_ver 0.5.1.0 +%global old_locale_ver 1.0.0.6 +%global old_time_ver 1.1.0.2 +%global pretty_ver 1.1.1.1 +%global process_ver 1.2.0.0 +%global template_haskell_ver 2.9.0.0 +%global terminfo_ver 0.4.0.0 +%global time_ver 1.4.2 +%global transformers_ver 0.3.0.0 +%global unix_ver 2.7.0.1 +%global xhtml_ver 3000.2.1 + # fedora ghc has been bootstrapped on # %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x @@ -103,11 +93,12 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -%if 0%{?fedora} >= 20 +%if 0%{?fedora} >= 20 || 0%{?rhel} >= 7 BuildRequires: ghc-rpm-macros-extra %else BuildRequires: ghc-rpm-macros %endif +BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -116,9 +107,9 @@ BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel BuildRequires: gmp-devel BuildRequires: libffi-devel -# for internal terminfo +# for terminfo BuildRequires: ncurses-devel -# for manpage and docs +# for man and docs BuildRequires: libxslt, docbook-style-xsl %if %{undefined without_testsuite} BuildRequires: python @@ -218,6 +209,7 @@ documention. # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes +%ghc_lib_subpackage haskeline %{haskeline_ver} %ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver} %ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver} %ghc_lib_subpackage hoopl %{hoopl_ver} @@ -229,8 +221,11 @@ documention. %ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} %undefine ghc_pkg_obsoletes %ghc_lib_subpackage template-haskell %{template_haskell_ver} +%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo %{terminfo_ver} %ghc_lib_subpackage time %{time_ver} +%ghc_lib_subpackage transformers %{transformers_ver} %ghc_lib_subpackage unix %{unix_ver} +%ghc_lib_subpackage xhtml %{xhtml_ver} %endif %global version %{ghc_version_override} @@ -258,24 +253,13 @@ except the ghc library, which is installed by the toplevel ghc metapackage. # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -# make sure we don't use these -rm -r ghc-tarballs/{mingw*,perl} -# use system libffi -%patch4 -p1 -b .libffi -rm -r ghc-tarballs/libffi -mkdir -p rts/dist/build -ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build - -%patch9 -p1 -b .orig +# unversion pkgdoc htmldir +rm -r libffi-tarballs %ifnarch %{ix86} x86_64 -%patch10 -p1 -b .10-ffi +#%%patch10 -p1 -b .10-ffi %endif -%patch12 -p1 -b .orig - -%patch13 -p1 -b .orig - %ifarch armv7hl armv5tel %patch14 -p1 -b .orig %endif @@ -288,10 +272,6 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch16 -p1 -b .orig %endif -%patch17 -p0 -b .orig - -#%%patch18 -p1 -b .orig - %ifarch ppc64le %patch19 -p1 -b .orig %endif @@ -342,8 +322,8 @@ BUILD_DOCBOOK_HTML = NO EOF export CFLAGS="${CFLAGS:-%optflags}" -# note %%configure induces cross-build due to different target/host/build platform names -# --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping +# * %%configure induces cross-build due to different target/host/build platform names +# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping %ifarch ppc64le aarch64 armv7hl for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i @@ -355,10 +335,11 @@ autoreconf --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc + --with-gcc=%{_bindir}/gcc --with-system-libffi -# utf8 is needed when building with verbose output -LANG=en_US.utf8 make %{?_smp_mflags} +# avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" +export LANG=en_US.utf8 +make %{?_smp_mflags} %install @@ -390,11 +371,15 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist bin-package-db ghc # add rts libs +echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files %if %{undefined ghc_without_shared} -ls %{buildroot}%{ghclibdir}/libHS*.so >> ghc-base.files -sed -i -e "s|^%{buildroot}||g" ghc-base.files +ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files %endif -ls -d %{buildroot}%{ghclibdir}/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files + +sed -i -e "s|^%{buildroot}||g" ghc-base.files + +ls -d %{buildroot}%{ghclibdir}/rts-1.0/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files + sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files # these are handled as alternatives @@ -421,8 +406,12 @@ sh %{gen_contents_index} --intree --verbose cd .. %endif +# we package the library license files separately +find %{buildroot}%ghclibdocdir -name LICENSE -exec rm '{}' ';' + %check +export LANG=en_US.utf8 # stolen from ghc6/debian/rules: GHC=inplace/bin/ghc-stage2 # Do some very simple tests that the compiler actually works @@ -477,7 +466,7 @@ fi %files %files compiler -%doc ANNOUNCE HACKING LICENSE README +%doc ANNOUNCE LICENSE %{_bindir}/ghc %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg @@ -491,18 +480,22 @@ fi %{_bindir}/runghc* %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc -%{ghclibdir}/ghc -%{ghclibdir}/ghc-pkg -# unknown ("unregisterized") archs +%dir %{ghclibdir}/bin +%{ghclibdir}/bin/ghc +%{ghclibdir}/bin/ghc-pkg +%{ghclibdir}/bin/hpc +%{ghclibdir}/bin/hsc2hs +%{ghclibdir}/bin/runghc +# unknown (unregisterized) archs %ifnarch ppc64 s390 s390x ppc64le aarch64 %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt -%{ghclibdir}/hsc2hs +%{ghclibdir}/mkGmpDerivedConstants %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache -%{ghclibdir}/runghc +%{ghclibdir}/platformConstants %{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit @@ -513,7 +506,7 @@ fi %{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} -%{ghclibdir}/haddock +%{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex %if %{undefined without_manual} @@ -547,6 +540,13 @@ fi %changelog +* Sun Aug 3 2014 Jens Petersen - 7.8.3-38 +- update to 7.8.3 +- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-1.html +- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-2.html +- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-3.html +- bootstrap build + * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) - only apply the Cabal unversion docdir patch to F21 and later diff --git a/sources b/sources index 40df58f..7878910 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -986d1f90ca30d60f7b2820d75c6b8ea7 ghc-7.6.3-src.tar.bz2 -66aa6177a31cc4b9d7eeb55cb1514918 ghc-7.6.3-testsuite.tar.bz2 +5e34b2a29564596c9ed83fb8667b47d4 ghc-7.8.3-src.tar.xz +7ca72a039d44ca2586c02863392b5dce ghc-7.8.3-testsuite.tar.xz From 883b428d41b6c15d3bd64dbea4b80086fc1ac0b5 Mon Sep 17 00:00:00 2001 From: Peter Robinson Date: Sat, 16 Aug 2014 14:26:57 +0000 Subject: [PATCH 373/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 23e000f..f33cc4d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 7.8.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 38%{?dist} +Release: 39%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -540,6 +540,9 @@ fi %changelog +* Sat Aug 16 2014 Fedora Release Engineering - 7.8.3-39 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild + * Sun Aug 3 2014 Jens Petersen - 7.8.3-38 - update to 7.8.3 - https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-1.html From a9ede5935e7f110aaf4015df2578aeaafe1595a6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 29 Aug 2014 17:01:38 +0900 Subject: [PATCH 374/530] change Cabal install bindir warning; drop use of ghc_without_shared --- ghc-7.8.3-Cabal-install-PATH-warning.patch | 12 ++++++++++++ ghc.spec | 16 +++++++--------- 2 files changed, 19 insertions(+), 9 deletions(-) create mode 100644 ghc-7.8.3-Cabal-install-PATH-warning.patch diff --git a/ghc-7.8.3-Cabal-install-PATH-warning.patch b/ghc-7.8.3-Cabal-install-PATH-warning.patch new file mode 100644 index 0000000..e7ef6e1 --- /dev/null +++ b/ghc-7.8.3-Cabal-install-PATH-warning.patch @@ -0,0 +1,12 @@ +--- ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2014-07-10 13:34:21.000000000 +0900 ++++ ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2014-08-29 16:48:12.621694879 +0900 +@@ -148,8 +148,7 @@ + notice verbosity ("Installing executable(s) in " ++ binPref) + inPath <- isInSearchPath binPref + when (not inPath) $ +- warn verbosity ("The directory " ++ binPref +- ++ " is not in the system search path.") ++ warn verbosity ("Executable installed in " ++ binPref) + + -- install include files for all compilers - they may be needed to compile + -- haskell files (using the CPP extension) diff --git a/ghc.spec b/ghc.spec index f33cc4d..7778771 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 7.8.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 39%{?dist} +Release: 38%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -38,6 +38,7 @@ Patch1: ghc-gen_contents_index-haddock-path.patch # add libffi include dir to ghc wrapper for archs using gcc/llc #Patch10: ghc-wrapper-libffi-include.patch # stop warnings about unsupported version of llvm +# NB: value affects ABI hash of libHSghc! Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch @@ -49,6 +50,7 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch +Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch %global Cabal_ver 1.18.1.3 %global array_ver 0.5.0.0 @@ -286,6 +288,7 @@ rm -r libffi-tarballs %patch22 -p1 -b .orig %endif +%patch23 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -307,7 +310,7 @@ BuildFlavour = perf BuildFlavour = perf-llvm %endif %endif -GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} +GhcLibWays = v dyn %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif @@ -372,9 +375,7 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files # add rts libs echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files -%if %{undefined ghc_without_shared} ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files -%endif sed -i -e "s|^%{buildroot}||g" ghc-base.files @@ -427,12 +428,10 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if %{undefined ghc_without_shared} echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%endif %if %{undefined without_testsuite} make test %endif @@ -540,15 +539,14 @@ fi %changelog -* Sat Aug 16 2014 Fedora Release Engineering - 7.8.3-39 -- Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild - * Sun Aug 3 2014 Jens Petersen - 7.8.3-38 - update to 7.8.3 - https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-1.html - https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-2.html - https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-3.html - bootstrap build +- provides haskeline, terminfo and xhtml libraries +- shared libraries on all archs * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) From 79a56ff15112c61f4621495ed1b06de56259d1dc Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 5 Sep 2014 12:41:51 +0900 Subject: [PATCH 375/530] use rpm internal dependency generator with ghc.attr on F22 requires ghc-rpm-macros ghc.attr - currently only in rawhide --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 7778771..c95675d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -187,13 +187,16 @@ The package provides a cronjob for re-indexing installed library development documention. %endif +# ghclibdir also needs ghc_version_override for bootstrapping (ghc-deps.sh) %global ghc_version_override %{version} +# currently only F22 ghc-rpm-macros has ghc.attr +%if 0%{?fedora} < 22 # needs ghc_version_override for bootstrapping %global _use_internal_dependency_generator 0 %global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} - +%endif %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} @@ -255,7 +258,6 @@ except the ghc library, which is installed by the toplevel ghc metapackage. # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -# unversion pkgdoc htmldir rm -r libffi-tarballs %ifnarch %{ix86} x86_64 @@ -270,6 +272,7 @@ rm -r libffi-tarballs %patch15 -p1 -b .orig %endif +# unversion pkgdoc htmldir %if 0%{?fedora} >= 21 %patch16 -p1 -b .orig %endif @@ -547,6 +550,7 @@ fi - bootstrap build - provides haskeline, terminfo and xhtml libraries - shared libraries on all archs +- use rpm internal dependency generator with ghc.attr on F22 * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) From fef35ff2f694df748dc3f38a91d2c45c1c1f4a2d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 29 Sep 2014 13:35:40 +0900 Subject: [PATCH 376/530] ghc-doc-index: drop bash-ism (#1146733) --- ghc-doc-index | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc-doc-index b/ghc-doc-index index 6105d7e..a0223fa 100755 --- a/ghc-doc-index +++ b/ghc-doc-index @@ -34,5 +34,5 @@ if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; the fi if [ -f $PKGDIRCACHE.new ]; then - mv -f $PKGDIRCACHE{.new,} + mv -f $PKGDIRCACHE.new $PKGDIRCACHE fi From 42c0b16fac6465736f0929ad04ab88bcb7261e36 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 29 Sep 2014 13:39:30 +0900 Subject: [PATCH 377/530] add changelog entry for bash-ism fix --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index c95675d..1a51dc1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -551,6 +551,7 @@ fi - provides haskeline, terminfo and xhtml libraries - shared libraries on all archs - use rpm internal dependency generator with ghc.attr on F22 +- fix bash-ism in ghc-doc-index (#1146733) * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) From 418016833e59fdb9f8b476e6221628692881421a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 1 Oct 2014 11:27:29 +0900 Subject: [PATCH 378/530] update Debian/Ubuntu arm64 patch to 7.8.3 --- ghc-arm64.patch | 220 ++++++++++++++++++++++++++++++++++++++---------- 1 file changed, 177 insertions(+), 43 deletions(-) diff --git a/ghc-arm64.patch b/ghc-arm64.patch index 06a7019..7652727 100644 --- a/ghc-arm64.patch +++ b/ghc-arm64.patch @@ -1,23 +1,27 @@ -Description: Add arm64 support -Author: Karel Gardas -Author: Colin Watson +commit c29bf984dd20431cd4344e8a5c444d7a5be08389 +Author: Colin Watson +Date: Mon Apr 21 22:26:56 2014 -0500 Bug: https://ghc.haskell.org/trac/ghc/ticket/7942 -Last-Update: 2014-04-04 -Index: b/aclocal.m4 + ghc: initial AArch64 patches + + Signed-off-by: Austin Seipp + +Index: ghc-7.8.3/aclocal.m4 =================================================================== ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -173,7 +173,7 @@ +--- ghc-7.8.3.orig/aclocal.m4 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/aclocal.m4 2014-07-10 10:16:42.529187516 +0200 +@@ -197,6 +197,9 @@ GET_ARM_ISA() test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" ;; -- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) -+ aarch64|alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" ++ aarch64) ++ test -z "[$]2" || eval "[$]2=ArchARM64" ++ ;; + alpha) + test -z "[$]2" || eval "[$]2=ArchAlpha" ;; - *) -@@ -1835,6 +1835,9 @@ +@@ -1862,6 +1865,9 @@ # converts cpu from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in @@ -27,29 +31,161 @@ Index: b/aclocal.m4 alpha*) $2="alpha" ;; -Index: b/includes/stg/MachRegs.h +Index: ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs =================================================================== ---- a/includes/stg/MachRegs.h -+++ b/includes/stg/MachRegs.h -@@ -43,6 +43,7 @@ - #define powerpc_REGS (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) - #define sparc_REGS sparc_TARGET_ARCH - #define arm_REGS arm_TARGET_ARCH -+#define aarch64_REGS aarch64_TARGET_ARCH - #define darwin_REGS darwin_TARGET_OS - #else - #define i386_REGS i386_HOST_ARCH -@@ -50,6 +51,7 @@ - #define powerpc_REGS (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH) - #define sparc_REGS sparc_HOST_ARCH - #define arm_REGS arm_HOST_ARCH -+#define aarch64_REGS aarch64_HOST_ARCH - #define darwin_REGS darwin_HOST_OS - #endif - -@@ -461,6 +463,63 @@ +--- ghc-7.8.3.orig/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.529187516 +0200 +@@ -166,6 +166,7 @@ + ArchPPC -> nCG' (ppcNcgImpl dflags) + ArchSPARC -> nCG' (sparcNcgImpl dflags) + ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" ++ ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" + ArchPPC_64 -> panic "nativeCodeGen: No NCG for PPC 64" + ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" + ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -113,6 +113,7 @@ + ArchSPARC -> 14 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -137,6 +138,7 @@ + ArchSPARC -> 22 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -161,6 +163,7 @@ + ArchSPARC -> 11 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -185,6 +188,7 @@ + ArchSPARC -> 0 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -74,6 +74,7 @@ + ArchPPC -> PPC.Instr.maxSpillSlots dflags + ArchSPARC -> SPARC.Instr.maxSpillSlots dflags + ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" ++ ArchARM64 -> panic "maxSpillSlots ArchARM64" + ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" + ArchAlpha -> panic "maxSpillSlots ArchAlpha" + ArchMipseb -> panic "maxSpillSlots ArchMipseb" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -207,6 +207,7 @@ + ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) first_id block_live sccs + ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs + ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" ++ ArchARM64 -> panic "linearRegAlloc ArchARM64" + ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" + ArchAlpha -> panic "linearRegAlloc ArchAlpha" + ArchMipseb -> panic "linearRegAlloc ArchMipseb" +Index: ghc-7.8.3/compiler/nativeGen/TargetReg.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -54,6 +54,7 @@ + ArchSPARC -> SPARC.virtualRegSqueeze + ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" + ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" ++ ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" + ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" + ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" + ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" +@@ -70,6 +71,7 @@ + ArchSPARC -> SPARC.realRegSqueeze + ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" + ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" ++ ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" + ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" + ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" + ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" +@@ -85,6 +87,7 @@ + ArchSPARC -> SPARC.classOfRealReg + ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" + ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" ++ ArchARM64 -> panic "targetClassOfRealReg ArchARM64" + ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" + ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" + ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" +@@ -100,6 +103,7 @@ + ArchSPARC -> SPARC.mkVirtualReg + ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" + ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" ++ ArchARM64 -> panic "targetMkVirtualReg ArchARM64" + ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" + ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" + ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" +@@ -115,6 +119,7 @@ + ArchSPARC -> SPARC.regDotColor + ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" + ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" ++ ArchARM64 -> panic "targetRegDotColor ArchARM64" + ArchAlpha -> panic "targetRegDotColor ArchAlpha" + ArchMipseb -> panic "targetRegDotColor ArchMipseb" + ArchMipsel -> panic "targetRegDotColor ArchMipsel" +Index: ghc-7.8.3/compiler/utils/Platform.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/utils/Platform.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/utils/Platform.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -52,6 +52,7 @@ + , armISAExt :: [ArmISAExt] + , armABI :: ArmABI + } ++ | ArchARM64 + | ArchAlpha + | ArchMipseb + | ArchMipsel +Index: ghc-7.8.3/includes/stg/HaskellMachRegs.h +=================================================================== +--- ghc-7.8.3.orig/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 +@@ -38,6 +38,7 @@ + #define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) + #define MACHREGS_sparc sparc_TARGET_ARCH + #define MACHREGS_arm arm_TARGET_ARCH ++#define MACHREGS_aarch64 aarch64_TARGET_ARCH + #define MACHREGS_darwin darwin_TARGET_OS - #endif /* arm */ + #endif +Index: ghc-7.8.3/includes/stg/MachRegs.h +=================================================================== +--- ghc-7.8.3.orig/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 +@@ -1,6 +1,6 @@ + /* ----------------------------------------------------------------------------- + * +- * (c) The GHC Team, 1998-2011 ++ * (c) The GHC Team, 1998-2014 + * + * Registers used in STG code. Might or might not correspond to + * actual machine registers. +@@ -531,6 +531,61 @@ + #define REG_D2 d11 + #endif +/* ----------------------------------------------------------------------------- + The ARMv8/AArch64 ABI register mapping @@ -83,7 +219,7 @@ Index: b/includes/stg/MachRegs.h + + ----------------------------------------------------------------------------- */ + -+#if aarch64_REGS ++#elif MACHREGS_aarch64 + +#define REG(x) __asm__(#x) + @@ -106,16 +242,14 @@ Index: b/includes/stg/MachRegs.h +#define REG_D1 d12 +#define REG_D2 d13 + -+#endif /* aarch64 */ -+ - #endif /* NO_REGS */ + #else - /* ----------------------------------------------------------------------------- -Index: b/rts/StgCRun.c + #error Cannot find platform to give register info for +Index: ghc-7.8.3/rts/StgCRun.c =================================================================== ---- a/rts/StgCRun.c -+++ b/rts/StgCRun.c -@@ -725,4 +725,70 @@ +--- ghc-7.8.3.orig/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 +@@ -748,4 +748,70 @@ } #endif From ba8410b35118cf91e8d65226b104331704f45ae6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 20 Oct 2014 11:43:44 +0900 Subject: [PATCH 379/530] - undefine ghc_without_shared if it is defined for now - ghc-ppc64el.patch is in 7.8.3 - use quick/quick-llvm when building - set LDFLAGS - probably no bindir/ghci now on archs without ghci --- ghc-ppc64el.patch | 41 ----------------------------------------- ghc.spec | 36 +++++++++++++++++++----------------- 2 files changed, 19 insertions(+), 58 deletions(-) delete mode 100644 ghc-ppc64el.patch diff --git a/ghc-ppc64el.patch b/ghc-ppc64el.patch deleted file mode 100644 index 9841054..0000000 --- a/ghc-ppc64el.patch +++ /dev/null @@ -1,41 +0,0 @@ -Description: Add ppc64el support -Author: Colin Watson -Bug: https://ghc.haskell.org/trac/ghc/ticket/8965 -Last-Update: 2014-04-12 - -Index: b/aclocal.m4 -=================================================================== ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -173,7 +173,7 @@ - GET_ARM_ISA() - test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" - ;; -- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) -+ alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" - ;; - *) -@@ -1868,6 +1868,9 @@ - mips*) - $2="mips" - ;; -+ powerpc64le*) -+ $2="powerpc64le" -+ ;; - powerpc64*) - $2="powerpc64" - ;; -Index: b/includes/Stg.h -=================================================================== ---- a/includes/Stg.h -+++ b/includes/Stg.h -@@ -213,7 +213,7 @@ - #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) - #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) - #define FN_(f) StgFunPtr f(void) --#define EF_(f) extern StgFunPtr f(void) -+#define EF_(f) extern StgFunPtr f() - - /* ----------------------------------------------------------------------------- - Tail calls diff --git a/ghc.spec b/ghc.spec index 1a51dc1..f303c6d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -10,6 +10,11 @@ ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock +# need to enable shared libs for all arches +%if %{defined ghc_without_shared} +%undefine ghc_without_shared +%endif + %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport @@ -42,9 +47,6 @@ Patch1: ghc-gen_contents_index-haddock-path.patch Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch -# changes for ppc64le committed upstream for 7.8.3 -# (https://ghc.haskell.org/trac/ghc/ticket/8965) -Patch19: ghc-ppc64el.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch @@ -119,11 +121,7 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif -%ifarch ppc64le aarch64 -# for patch19 and patch21 -BuildRequires: autoconf -%endif -%ifarch armv7hl +%ifarch armv7hl aarch64 # patch22 BuildRequires: autoconf, automake %endif @@ -268,19 +266,11 @@ rm -r libffi-tarballs %patch14 -p1 -b .orig %endif -%ifarch ppc64 s390x -%patch15 -p1 -b .orig -%endif - # unversion pkgdoc htmldir %if 0%{?fedora} >= 21 %patch16 -p1 -b .orig %endif -%ifarch ppc64le -%patch19 -p1 -b .orig -%endif - %patch20 -p1 -b .orig %ifarch aarch64 @@ -312,6 +302,12 @@ BuildFlavour = perf %else BuildFlavour = perf-llvm %endif +%else +%ifnarch armv7hl armv5tel +BuildFlavour = quick-llvm +%else +BuildFlavour = quick +%endif %endif GhcLibWays = v dyn %{!?without_prof:p} %if %{defined without_haddock} @@ -328,9 +324,10 @@ BUILD_DOCBOOK_HTML = NO EOF export CFLAGS="${CFLAGS:-%optflags}" +export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # * %%configure induces cross-build due to different target/host/build platform names # * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping -%ifarch ppc64le aarch64 armv7hl +%ifarch aarch64 armv7hl for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done @@ -473,8 +470,10 @@ fi %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} +%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} +%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -552,6 +551,9 @@ fi - shared libraries on all archs - use rpm internal dependency generator with ghc.attr on F22 - fix bash-ism in ghc-doc-index (#1146733) +- do "quick" build when bootstrapping +- setup LDFLAGS +- bindir/ghci only on ghc_arches_with_ghci * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) From 7c993482d16207515796c3a3c20dd28be00e52ec Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 5 Nov 2014 12:28:37 +0900 Subject: [PATCH 380/530] update patches for armv7 for ghc-7.8 - LlvmCodeGen-llvm-version-warning patch no needed since 3.4 supported now, but rawhide is now on 3.5! - update no NEON patch --- ...ON.patch => ghc-armv7-VFPv3D16--NEON.patch | 8 +++---- ghc.spec | 22 +++++++++++-------- 2 files changed, 17 insertions(+), 13 deletions(-) rename ghc-7.6.3-armv7-VFPv3D16--NEON.patch => ghc-armv7-VFPv3D16--NEON.patch (58%) diff --git a/ghc-7.6.3-armv7-VFPv3D16--NEON.patch b/ghc-armv7-VFPv3D16--NEON.patch similarity index 58% rename from ghc-7.6.3-armv7-VFPv3D16--NEON.patch rename to ghc-armv7-VFPv3D16--NEON.patch index 6412ff5..e51a353 100644 --- a/ghc-7.6.3-armv7-VFPv3D16--NEON.patch +++ b/ghc-armv7-VFPv3D16--NEON.patch @@ -1,7 +1,7 @@ ---- ghc-7.6.3/aclocal.m4~ 2013-04-19 06:22:46.000000000 +0900 -+++ ghc-7.6.3/aclocal.m4 2014-07-15 18:22:12.308929288 +0900 -@@ -349,7 +349,7 @@ - ], +--- ghc-7.8.3/aclocal.m4~ 2014-07-10 13:27:16.000000000 +0900 ++++ ghc-7.8.3/aclocal.m4 2014-11-05 12:19:08.530044128 +0900 +@@ -408,7 +408,7 @@ + )], [changequote(, )dnl ARM_ISA=ARMv7 - ARM_ISA_EXT="[VFPv3,NEON]" diff --git a/ghc.spec b/ghc.spec index f303c6d..6c63e70 100644 --- a/ghc.spec +++ b/ghc.spec @@ -44,14 +44,15 @@ Patch1: ghc-gen_contents_index-haddock-path.patch #Patch10: ghc-wrapper-libffi-include.patch # stop warnings about unsupported version of llvm # NB: value affects ABI hash of libHSghc! -Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch +# will probably be needed again for llvm-3.5 +#Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch -Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch +Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch %global Cabal_ver 1.18.1.3 @@ -84,7 +85,8 @@ Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch # fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x +# %{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 +# and retired arches: alpha sparcv9 armv5tel # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros ExcludeArch: sparc64 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 @@ -263,7 +265,7 @@ rm -r libffi-tarballs %endif %ifarch armv7hl armv5tel -%patch14 -p1 -b .orig +#%%patch14 -p1 -b .orig %endif # unversion pkgdoc htmldir @@ -323,16 +325,18 @@ BUILD_DOCBOOK_HTML = NO #EXTRA_HC_OPTS=-debug EOF -export CFLAGS="${CFLAGS:-%optflags}" -export LDFLAGS="${LDFLAGS:-%__global_ldflags}" -# * %%configure induces cross-build due to different target/host/build platform names -# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping -%ifarch aarch64 armv7hl +%ifarch aarch64 for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done +%endif +%ifarch aarch64 armv7hl autoreconf %endif +export CFLAGS="${CFLAGS:-%optflags}" +export LDFLAGS="${LDFLAGS:-%__global_ldflags}" +# * %%configure induces cross-build due to different target/host/build platform names +# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ From 9d76b15c80e1d878be079d62c4c7c2ee392e8e0d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 17 Nov 2014 12:24:08 +0900 Subject: [PATCH 381/530] revert to 7.6.3-26 (current f21) --- ...executable-stack-for-the-linker-note.patch | 37 --- ...ch => ghc-7.6.3-armv7-VFPv3D16--NEON.patch | 8 +- ghc-7.8.3-Cabal-install-PATH-warning.patch | 12 - ghc-NCG-no-execstack.patch | 32 --- ghc-arm64.patch | 220 ++++------------ ghc-cabal-unversion-docdir.patch | 26 +- ghc-doc-index | 2 +- ghc-ppc64el.patch | 41 +++ ghc.spec | 241 +++++++++--------- sources | 4 +- 10 files changed, 220 insertions(+), 403 deletions(-) delete mode 100644 ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch rename ghc-armv7-VFPv3D16--NEON.patch => ghc-7.6.3-armv7-VFPv3D16--NEON.patch (58%) delete mode 100644 ghc-7.8.3-Cabal-install-PATH-warning.patch delete mode 100644 ghc-NCG-no-execstack.patch create mode 100644 ghc-ppc64el.patch diff --git a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch deleted file mode 100644 index 63583af..0000000 --- a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch +++ /dev/null @@ -1,37 +0,0 @@ -From 08a38628f29df63ac842f4d083efb414f42d7bff Mon Sep 17 00:00:00 2001 -From: "Edward Z. Yang" -Date: Tue, 9 Jul 2013 00:01:43 -0700 -Subject: [PATCH] Disable executable stack for the linker note, fixing #703 - (again) - -Signed-off-by: Edward Z. Yang ---- - compiler/main/DriverPipeline.hs | 12 +++++++++++- - 1 file changed, 11 insertions(+), 1 deletion(-) - -diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs -index 67377e6..26425ae 100644 ---- a/compiler/main/DriverPipeline.hs -+++ b/compiler/main/DriverPipeline.hs -@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do - text elfSectionNote, - text "\n", - -- text "\t.ascii \"", info', text "\"\n" ] -+ text "\t.ascii \"", info', text "\"\n", -+ -+ -- ALL generated assembly must have this section to disable -+ -- executable stacks. See also -+ -- compiler/nativeGen/AsmCodeGen.lhs for another instance -+ -- where we need to do this. -+ (if platformHasGnuNonexecStack (targetPlatform dflags) -+ then text ".section .note.GNU-stack,\"\",@progbits\n" -+ else empty) -+ -+ ] - where - info' = text $ escape info - --- -1.8.1.2 - diff --git a/ghc-armv7-VFPv3D16--NEON.patch b/ghc-7.6.3-armv7-VFPv3D16--NEON.patch similarity index 58% rename from ghc-armv7-VFPv3D16--NEON.patch rename to ghc-7.6.3-armv7-VFPv3D16--NEON.patch index e51a353..6412ff5 100644 --- a/ghc-armv7-VFPv3D16--NEON.patch +++ b/ghc-7.6.3-armv7-VFPv3D16--NEON.patch @@ -1,7 +1,7 @@ ---- ghc-7.8.3/aclocal.m4~ 2014-07-10 13:27:16.000000000 +0900 -+++ ghc-7.8.3/aclocal.m4 2014-11-05 12:19:08.530044128 +0900 -@@ -408,7 +408,7 @@ - )], +--- ghc-7.6.3/aclocal.m4~ 2013-04-19 06:22:46.000000000 +0900 ++++ ghc-7.6.3/aclocal.m4 2014-07-15 18:22:12.308929288 +0900 +@@ -349,7 +349,7 @@ + ], [changequote(, )dnl ARM_ISA=ARMv7 - ARM_ISA_EXT="[VFPv3,NEON]" diff --git a/ghc-7.8.3-Cabal-install-PATH-warning.patch b/ghc-7.8.3-Cabal-install-PATH-warning.patch deleted file mode 100644 index e7ef6e1..0000000 --- a/ghc-7.8.3-Cabal-install-PATH-warning.patch +++ /dev/null @@ -1,12 +0,0 @@ ---- ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2014-07-10 13:34:21.000000000 +0900 -+++ ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2014-08-29 16:48:12.621694879 +0900 -@@ -148,8 +148,7 @@ - notice verbosity ("Installing executable(s) in " ++ binPref) - inPath <- isInSearchPath binPref - when (not inPath) $ -- warn verbosity ("The directory " ++ binPref -- ++ " is not in the system search path.") -+ warn verbosity ("Executable installed in " ++ binPref) - - -- install include files for all compilers - they may be needed to compile - -- haskell files (using the CPP extension) diff --git a/ghc-NCG-no-execstack.patch b/ghc-NCG-no-execstack.patch deleted file mode 100644 index 40b6ba6..0000000 --- a/ghc-NCG-no-execstack.patch +++ /dev/null @@ -1,32 +0,0 @@ -commit 08a38628f29df63ac842f4d083efb414f42d7bff -Author: Edward Z. Yang -Date: Tue Jul 9 00:01:43 2013 -0700 - - Disable executable stack for the linker note, fixing #703 (again) - - Signed-off-by: Edward Z. Yang - - Modified compiler/main/DriverPipeline.hs -diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs -index 67377e6..26425ae 100644 ---- a/compiler/main/DriverPipeline.hs -+++ b/compiler/main/DriverPipeline.hs -@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do - text elfSectionNote, - text "\n", - -- text "\t.ascii \"", info', text "\"\n" ] -+ text "\t.ascii \"", info', text "\"\n", -+ -+ -- ALL generated assembly must have this section to disable -+ -- executable stacks. See also -+ -- compiler/nativeGen/AsmCodeGen.lhs for another instance -+ -- where we need to do this. -+ (if platformHasGnuNonexecStack (targetPlatform dflags) -+ then text ".section .note.GNU-stack,\"\",@progbits\n" -+ else empty) -+ -+ ] - where - info' = text $ escape info - diff --git a/ghc-arm64.patch b/ghc-arm64.patch index 7652727..06a7019 100644 --- a/ghc-arm64.patch +++ b/ghc-arm64.patch @@ -1,27 +1,23 @@ -commit c29bf984dd20431cd4344e8a5c444d7a5be08389 -Author: Colin Watson -Date: Mon Apr 21 22:26:56 2014 -0500 +Description: Add arm64 support +Author: Karel Gardas +Author: Colin Watson Bug: https://ghc.haskell.org/trac/ghc/ticket/7942 +Last-Update: 2014-04-04 - ghc: initial AArch64 patches - - Signed-off-by: Austin Seipp - -Index: ghc-7.8.3/aclocal.m4 +Index: b/aclocal.m4 =================================================================== ---- ghc-7.8.3.orig/aclocal.m4 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/aclocal.m4 2014-07-10 10:16:42.529187516 +0200 -@@ -197,6 +197,9 @@ +--- a/aclocal.m4 ++++ b/aclocal.m4 +@@ -173,7 +173,7 @@ GET_ARM_ISA() test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" ;; -+ aarch64) -+ test -z "[$]2" || eval "[$]2=ArchARM64" -+ ;; - alpha) - test -z "[$]2" || eval "[$]2=ArchAlpha" +- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) ++ aarch64|alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) + test -z "[$]2" || eval "[$]2=ArchUnknown" ;; -@@ -1862,6 +1865,9 @@ + *) +@@ -1835,6 +1835,9 @@ # converts cpu from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in @@ -31,162 +27,30 @@ Index: ghc-7.8.3/aclocal.m4 alpha*) $2="alpha" ;; -Index: ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.529187516 +0200 -@@ -166,6 +166,7 @@ - ArchPPC -> nCG' (ppcNcgImpl dflags) - ArchSPARC -> nCG' (sparcNcgImpl dflags) - ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" -+ ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" - ArchPPC_64 -> panic "nativeCodeGen: No NCG for PPC 64" - ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" - ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -113,6 +113,7 @@ - ArchSPARC -> 14 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -137,6 +138,7 @@ - ArchSPARC -> 22 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -161,6 +163,7 @@ - ArchSPARC -> 11 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -185,6 +188,7 @@ - ArchSPARC -> 0 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -74,6 +74,7 @@ - ArchPPC -> PPC.Instr.maxSpillSlots dflags - ArchSPARC -> SPARC.Instr.maxSpillSlots dflags - ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" -+ ArchARM64 -> panic "maxSpillSlots ArchARM64" - ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" - ArchAlpha -> panic "maxSpillSlots ArchAlpha" - ArchMipseb -> panic "maxSpillSlots ArchMipseb" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -207,6 +207,7 @@ - ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) first_id block_live sccs - ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs - ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" -+ ArchARM64 -> panic "linearRegAlloc ArchARM64" - ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" - ArchAlpha -> panic "linearRegAlloc ArchAlpha" - ArchMipseb -> panic "linearRegAlloc ArchMipseb" -Index: ghc-7.8.3/compiler/nativeGen/TargetReg.hs +Index: b/includes/stg/MachRegs.h =================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -54,6 +54,7 @@ - ArchSPARC -> SPARC.virtualRegSqueeze - ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" - ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" -+ ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" - ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" - ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" - ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" -@@ -70,6 +71,7 @@ - ArchSPARC -> SPARC.realRegSqueeze - ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" - ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" -+ ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" - ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" - ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" - ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" -@@ -85,6 +87,7 @@ - ArchSPARC -> SPARC.classOfRealReg - ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" - ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" -+ ArchARM64 -> panic "targetClassOfRealReg ArchARM64" - ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" - ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" - ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" -@@ -100,6 +103,7 @@ - ArchSPARC -> SPARC.mkVirtualReg - ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" - ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" -+ ArchARM64 -> panic "targetMkVirtualReg ArchARM64" - ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" - ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" - ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" -@@ -115,6 +119,7 @@ - ArchSPARC -> SPARC.regDotColor - ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" - ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" -+ ArchARM64 -> panic "targetRegDotColor ArchARM64" - ArchAlpha -> panic "targetRegDotColor ArchAlpha" - ArchMipseb -> panic "targetRegDotColor ArchMipseb" - ArchMipsel -> panic "targetRegDotColor ArchMipsel" -Index: ghc-7.8.3/compiler/utils/Platform.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/utils/Platform.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/utils/Platform.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -52,6 +52,7 @@ - , armISAExt :: [ArmISAExt] - , armABI :: ArmABI - } -+ | ArchARM64 - | ArchAlpha - | ArchMipseb - | ArchMipsel -Index: ghc-7.8.3/includes/stg/HaskellMachRegs.h -=================================================================== ---- ghc-7.8.3.orig/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 -@@ -38,6 +38,7 @@ - #define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) - #define MACHREGS_sparc sparc_TARGET_ARCH - #define MACHREGS_arm arm_TARGET_ARCH -+#define MACHREGS_aarch64 aarch64_TARGET_ARCH - #define MACHREGS_darwin darwin_TARGET_OS - - #endif -Index: ghc-7.8.3/includes/stg/MachRegs.h -=================================================================== ---- ghc-7.8.3.orig/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 -@@ -1,6 +1,6 @@ - /* ----------------------------------------------------------------------------- - * -- * (c) The GHC Team, 1998-2011 -+ * (c) The GHC Team, 1998-2014 - * - * Registers used in STG code. Might or might not correspond to - * actual machine registers. -@@ -531,6 +531,61 @@ - #define REG_D2 d11 +--- a/includes/stg/MachRegs.h ++++ b/includes/stg/MachRegs.h +@@ -43,6 +43,7 @@ + #define powerpc_REGS (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) + #define sparc_REGS sparc_TARGET_ARCH + #define arm_REGS arm_TARGET_ARCH ++#define aarch64_REGS aarch64_TARGET_ARCH + #define darwin_REGS darwin_TARGET_OS + #else + #define i386_REGS i386_HOST_ARCH +@@ -50,6 +51,7 @@ + #define powerpc_REGS (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH) + #define sparc_REGS sparc_HOST_ARCH + #define arm_REGS arm_HOST_ARCH ++#define aarch64_REGS aarch64_HOST_ARCH + #define darwin_REGS darwin_HOST_OS #endif +@@ -461,6 +463,63 @@ + + #endif /* arm */ + +/* ----------------------------------------------------------------------------- + The ARMv8/AArch64 ABI register mapping + @@ -219,7 +83,7 @@ Index: ghc-7.8.3/includes/stg/MachRegs.h + + ----------------------------------------------------------------------------- */ + -+#elif MACHREGS_aarch64 ++#if aarch64_REGS + +#define REG(x) __asm__(#x) + @@ -242,14 +106,16 @@ Index: ghc-7.8.3/includes/stg/MachRegs.h +#define REG_D1 d12 +#define REG_D2 d13 + - #else ++#endif /* aarch64 */ ++ + #endif /* NO_REGS */ - #error Cannot find platform to give register info for -Index: ghc-7.8.3/rts/StgCRun.c + /* ----------------------------------------------------------------------------- +Index: b/rts/StgCRun.c =================================================================== ---- ghc-7.8.3.orig/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 -@@ -748,4 +748,70 @@ +--- a/rts/StgCRun.c ++++ b/rts/StgCRun.c +@@ -725,4 +725,70 @@ } #endif diff --git a/ghc-cabal-unversion-docdir.patch b/ghc-cabal-unversion-docdir.patch index 9d0b026..0aefeb5 100644 --- a/ghc-cabal-unversion-docdir.patch +++ b/ghc-cabal-unversion-docdir.patch @@ -1,13 +1,13 @@ ---- ghc-7.8/utils/ghc-cabal/Main.hs~ 2013-08-28 08:06:37.000000000 +0900 -+++ ghc-7.8/utils/ghc-cabal/Main.hs 2013-09-03 17:51:22.800653817 +0900 -@@ -251,8 +251,8 @@ - libsubdir = toPathTemplate "$pkgid", - docdir = toPathTemplate $ - if relocatableBuild -- then "$topdir/../doc/html/libraries/$pkgid" -- else (myDocdir "$pkgid"), -+ then "$topdir/../doc/html/libraries/$pkg" -+ else (myDocdir "$pkg"), - htmldir = toPathTemplate "$docdir" - } - +--- ghc-7.6.3/utils/ghc-cabal/Main.hs~ 2013-04-19 06:22:47.000000000 +0900 ++++ ghc-7.6.3/utils/ghc-cabal/Main.hs 2013-10-29 12:35:18.916340631 +0900 +@@ -180,8 +180,8 @@ + libsubdir = toPathTemplate "$pkgid", + docdir = toPathTemplate $ + if relocatableBuild +- then "$topdir/../doc/html/libraries/$pkgid" +- else (myDocdir "$pkgid"), ++ then "$topdir/../doc/html/libraries/$pkg" ++ else (myDocdir "$pkg"), + htmldir = toPathTemplate "$docdir" + } + progs = withPrograms lbi diff --git a/ghc-doc-index b/ghc-doc-index index a0223fa..6105d7e 100755 --- a/ghc-doc-index +++ b/ghc-doc-index @@ -34,5 +34,5 @@ if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; the fi if [ -f $PKGDIRCACHE.new ]; then - mv -f $PKGDIRCACHE.new $PKGDIRCACHE + mv -f $PKGDIRCACHE{.new,} fi diff --git a/ghc-ppc64el.patch b/ghc-ppc64el.patch new file mode 100644 index 0000000..9841054 --- /dev/null +++ b/ghc-ppc64el.patch @@ -0,0 +1,41 @@ +Description: Add ppc64el support +Author: Colin Watson +Bug: https://ghc.haskell.org/trac/ghc/ticket/8965 +Last-Update: 2014-04-12 + +Index: b/aclocal.m4 +=================================================================== +--- a/aclocal.m4 ++++ b/aclocal.m4 +@@ -173,7 +173,7 @@ + GET_ARM_ISA() + test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" + ;; +- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) ++ alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) + test -z "[$]2" || eval "[$]2=ArchUnknown" + ;; + *) +@@ -1868,6 +1868,9 @@ + mips*) + $2="mips" + ;; ++ powerpc64le*) ++ $2="powerpc64le" ++ ;; + powerpc64*) + $2="powerpc64" + ;; +Index: b/includes/Stg.h +=================================================================== +--- a/includes/Stg.h ++++ b/includes/Stg.h +@@ -213,7 +213,7 @@ + #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) + #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) + #define FN_(f) StgFunPtr f(void) +-#define EF_(f) extern StgFunPtr f(void) ++#define EF_(f) extern StgFunPtr f() + + /* ----------------------------------------------------------------------------- + Tail calls diff --git a/ghc.spec b/ghc.spec index 6c63e70..44e4922 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,92 +1,96 @@ +# Shared haskell libraries are supported for x86* archs +# (disabled for other archs in ghc-rpm-macros) + # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%global without_testsuite 1 -%global without_prof 1 -%if 0%{?fedora} >= 22 -%{?ghc_bootstrap} -%else -%{?ghc_test} -%endif +#%%global ghc_bootstrapping 1 +#%%global without_testsuite 1 +### either: +#%%{?ghc_bootstrap} +### or for shared libs: +#%%{?ghc_test} ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock -# need to enable shared libs for all arches -%if %{defined ghc_without_shared} -%undefine ghc_without_shared -%endif - %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.8.3 +Version: 7.6.3 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -# xhtml moved from haskell-platform to ghc-7.8.3 -Release: 38%{?dist} +Release: 26%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport URL: http://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 %if %{undefined without_testsuite} -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch +# fedora does not allow copy libraries +Patch4: ghc-use-system-libffi.patch +# fix dynamic linking of executables using Template Haskell +Patch9: Cabal-fix-dynamic-exec-for-TH.patch # add libffi include dir to ghc wrapper for archs using gcc/llc -#Patch10: ghc-wrapper-libffi-include.patch +Patch10: ghc-wrapper-libffi-include.patch +# disable building HS*.o libs for ghci +Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch +# fix compilation with llvm-3.3 +Patch13: ghc-llvmCodeGen-empty-array.patch # stop warnings about unsupported version of llvm -# NB: value affects ABI hash of libHSghc! -# will probably be needed again for llvm-3.5 -#Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch +Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch +# fix hang on ppc64 and s390x (upstream in 7.8) +Patch15: ghc-64bit-bigendian-rts-hang-989593.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch +# fix libffi segfaults on 32bit (upstream in 7.8) +Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch +# add .note.GNU-stack to assembly output to avoid execstack (#973512) +# (disabled for now since it changes libghc ABI and fix only works for i686) +#Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch +# changes for ppc64le committed upstream for 7.8.3 +# (https://ghc.haskell.org/trac/ghc/ticket/8965) +Patch19: ghc-ppc64el.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch -Patch22: ghc-armv7-VFPv3D16--NEON.patch -Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch +Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch -%global Cabal_ver 1.18.1.3 -%global array_ver 0.5.0.0 -%global base_ver 4.7.0.1 +%global Cabal_ver 1.16.0 +%global array_ver 0.4.0.1 +%global base_ver 4.6.0.1 %global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.7.1.0 -%global bytestring_ver 0.10.4.0 -%global containers_ver 0.5.5.1 -%global deepseq_ver 1.3.0.2 -%global directory_ver 1.2.1.0 -%global filepath_ver 1.3.0.2 -%global ghc_prim_ver 0.3.1.0 -%global haskeline_ver 0.7.1.2 -%global haskell2010_ver 1.1.2.0 -%global haskell98_ver 2.0.0.3 -%global hoopl_ver 3.10.0.1 -%global hpc_ver 0.6.0.1 -%global integer_gmp_ver 0.5.1.0 -%global old_locale_ver 1.0.0.6 -%global old_time_ver 1.1.0.2 -%global pretty_ver 1.1.1.1 -%global process_ver 1.2.0.0 -%global template_haskell_ver 2.9.0.0 -%global terminfo_ver 0.4.0.0 -%global time_ver 1.4.2 -%global transformers_ver 0.3.0.0 -%global unix_ver 2.7.0.1 -%global xhtml_ver 3000.2.1 - +%global binary_ver 0.5.1.1 +%global bytestring_ver 0.10.0.2 +%global containers_ver 0.5.0.0 +%global deepseq_ver 1.3.0.1 +%global directory_ver 1.2.0.1 +%global filepath_ver 1.3.0.1 +%global ghc_prim_ver 0.3.0.0 +%global haskell2010_ver 1.1.1.0 +%global haskell98_ver 2.0.0.2 +%global hoopl_ver 3.9.0.0 +%global hpc_ver 0.6.0.0 +%global integer_gmp_ver 0.5.0.0 +%global old_locale_ver 1.0.0.5 +%global old_time_ver 1.1.0.1 +%global pretty_ver 1.1.1.0 +%global process_ver 1.1.0.2 +%global template_haskell_ver 2.8.0.0 +%global time_ver 1.4.0.1 +%global unix_ver 2.6.0.1 # fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 -# and retired arches: alpha sparcv9 armv5tel +# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros ExcludeArch: sparc64 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 @@ -99,12 +103,11 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -%if 0%{?fedora} >= 20 || 0%{?rhel} >= 7 +%if 0%{?fedora} >= 20 BuildRequires: ghc-rpm-macros-extra %else BuildRequires: ghc-rpm-macros %endif -BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -113,9 +116,9 @@ BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel BuildRequires: gmp-devel BuildRequires: libffi-devel -# for terminfo +# for internal terminfo BuildRequires: ncurses-devel -# for man and docs +# for manpage and docs BuildRequires: libxslt, docbook-style-xsl %if %{undefined without_testsuite} BuildRequires: python @@ -123,7 +126,11 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm >= 3.0 %endif -%ifarch armv7hl aarch64 +%ifarch ppc64le aarch64 +# for patch19 and patch21 +BuildRequires: autoconf +%endif +%ifarch armv7hl # patch22 BuildRequires: autoconf, automake %endif @@ -187,16 +194,13 @@ The package provides a cronjob for re-indexing installed library development documention. %endif -# ghclibdir also needs ghc_version_override for bootstrapping (ghc-deps.sh) %global ghc_version_override %{version} -# currently only F22 ghc-rpm-macros has ghc.attr -%if 0%{?fedora} < 22 # needs ghc_version_override for bootstrapping %global _use_internal_dependency_generator 0 %global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} -%endif + %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} @@ -214,7 +218,6 @@ documention. # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage haskeline %{haskeline_ver} %ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver} %ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver} %ghc_lib_subpackage hoopl %{hoopl_ver} @@ -226,11 +229,8 @@ documention. %ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} %undefine ghc_pkg_obsoletes %ghc_lib_subpackage template-haskell %{template_haskell_ver} -%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo %{terminfo_ver} %ghc_lib_subpackage time %{time_ver} -%ghc_lib_subpackage transformers %{transformers_ver} %ghc_lib_subpackage unix %{unix_ver} -%ghc_lib_subpackage xhtml %{xhtml_ver} %endif %global version %{ghc_version_override} @@ -258,21 +258,44 @@ except the ghc library, which is installed by the toplevel ghc metapackage. # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -rm -r libffi-tarballs +# make sure we don't use these +rm -r ghc-tarballs/{mingw*,perl} +# use system libffi +%patch4 -p1 -b .libffi +rm -r ghc-tarballs/libffi +mkdir -p rts/dist/build +ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build + +%patch9 -p1 -b .orig %ifnarch %{ix86} x86_64 -#%%patch10 -p1 -b .10-ffi +%patch10 -p1 -b .10-ffi %endif +%patch12 -p1 -b .orig + +%patch13 -p1 -b .orig + %ifarch armv7hl armv5tel -#%%patch14 -p1 -b .orig +%patch14 -p1 -b .orig +%endif + +%ifarch ppc64 s390x +%patch15 -p1 -b .orig %endif -# unversion pkgdoc htmldir %if 0%{?fedora} >= 21 %patch16 -p1 -b .orig %endif +%patch17 -p0 -b .orig + +#%%patch18 -p1 -b .orig + +%ifarch ppc64le +%patch19 -p1 -b .orig +%endif + %patch20 -p1 -b .orig %ifarch aarch64 @@ -283,7 +306,6 @@ rm -r libffi-tarballs %patch22 -p1 -b .orig %endif -%patch23 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -304,14 +326,8 @@ BuildFlavour = perf %else BuildFlavour = perf-llvm %endif -%else -%ifnarch armv7hl armv5tel -BuildFlavour = quick-llvm -%else -BuildFlavour = quick -%endif %endif -GhcLibWays = v dyn %{!?without_prof:p} +GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif @@ -325,28 +341,24 @@ BUILD_DOCBOOK_HTML = NO #EXTRA_HC_OPTS=-debug EOF -%ifarch aarch64 +export CFLAGS="${CFLAGS:-%optflags}" +# note %%configure induces cross-build due to different target/host/build platform names +# --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping +%ifarch ppc64le aarch64 armv7hl for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done -%endif -%ifarch aarch64 armv7hl autoreconf %endif -export CFLAGS="${CFLAGS:-%optflags}" -export LDFLAGS="${LDFLAGS:-%__global_ldflags}" -# * %%configure induces cross-build due to different target/host/build platform names -# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc --with-system-libffi + --with-gcc=%{_bindir}/gcc -# avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" -export LANG=en_US.utf8 -make %{?_smp_mflags} +# utf8 is needed when building with verbose output +LANG=en_US.utf8 make %{?_smp_mflags} %install @@ -378,13 +390,11 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist bin-package-db ghc # add rts libs -echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files -ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files - +%if %{undefined ghc_without_shared} +ls %{buildroot}%{ghclibdir}/libHS*.so >> ghc-base.files sed -i -e "s|^%{buildroot}||g" ghc-base.files - -ls -d %{buildroot}%{ghclibdir}/rts-1.0/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files - +%endif +ls -d %{buildroot}%{ghclibdir}/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files # these are handled as alternatives @@ -411,12 +421,8 @@ sh %{gen_contents_index} --intree --verbose cd .. %endif -# we package the library license files separately -find %{buildroot}%ghclibdocdir -name LICENSE -exec rm '{}' ';' - %check -export LANG=en_US.utf8 # stolen from ghc6/debian/rules: GHC=inplace/bin/ghc-stage2 # Do some very simple tests that the compiler actually works @@ -432,10 +438,12 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* +%if %{undefined ghc_without_shared} echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* +%endif %if %{undefined without_testsuite} make test %endif @@ -469,15 +477,13 @@ fi %files %files compiler -%doc ANNOUNCE LICENSE +%doc ANNOUNCE HACKING LICENSE README %{_bindir}/ghc %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} -%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} -%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -485,22 +491,18 @@ fi %{_bindir}/runghc* %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc -%dir %{ghclibdir}/bin -%{ghclibdir}/bin/ghc -%{ghclibdir}/bin/ghc-pkg -%{ghclibdir}/bin/hpc -%{ghclibdir}/bin/hsc2hs -%{ghclibdir}/bin/runghc -# unknown (unregisterized) archs +%{ghclibdir}/ghc +%{ghclibdir}/ghc-pkg +# unknown ("unregisterized") archs %ifnarch ppc64 s390 s390x ppc64le aarch64 %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt -%{ghclibdir}/mkGmpDerivedConstants +%{ghclibdir}/hsc2hs %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache -%{ghclibdir}/platformConstants +%{ghclibdir}/runghc %{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit @@ -511,7 +513,7 @@ fi %{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} -%{ghclibdir}/bin/haddock +%{ghclibdir}/haddock %{ghclibdir}/html %{ghclibdir}/latex %if %{undefined without_manual} @@ -545,19 +547,8 @@ fi %changelog -* Sun Aug 3 2014 Jens Petersen - 7.8.3-38 -- update to 7.8.3 -- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-1.html -- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-2.html -- https://www.haskell.org/ghc/docs/7.8.3/html/users_guide/release-7-8-3.html -- bootstrap build -- provides haskeline, terminfo and xhtml libraries -- shared libraries on all archs -- use rpm internal dependency generator with ghc.attr on F22 -- fix bash-ism in ghc-doc-index (#1146733) -- do "quick" build when bootstrapping -- setup LDFLAGS -- bindir/ghci only on ghc_arches_with_ghci +* Sat Aug 16 2014 Fedora Release Engineering - 7.6.3-26 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild * Tue Jul 15 2014 Jens Petersen - 7.6.3-25 - configure ARM with VFPv3D16 and without NEON (#995419) diff --git a/sources b/sources index 7878910..40df58f 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -5e34b2a29564596c9ed83fb8667b47d4 ghc-7.8.3-src.tar.xz -7ca72a039d44ca2586c02863392b5dce ghc-7.8.3-testsuite.tar.xz +986d1f90ca30d60f7b2820d75c6b8ea7 ghc-7.6.3-src.tar.bz2 +66aa6177a31cc4b9d7eeb55cb1514918 ghc-7.6.3-testsuite.tar.bz2 From 6977ee8fbfd5ff92b5fe7b1ea92b1fdcb06585f0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 17 Nov 2014 17:53:19 +0900 Subject: [PATCH 382/530] require and use llvm34 instead of llvm-3.5 for arm --- ghc | 3 +++ ghc-pkg | 3 +++ ghc.spec | 20 ++++++++++++++++---- 3 files changed, 22 insertions(+), 4 deletions(-) create mode 100755 ghc create mode 100755 ghc-pkg diff --git a/ghc b/ghc new file mode 100755 index 0000000..aa61e6a --- /dev/null +++ b/ghc @@ -0,0 +1,3 @@ +#!/bin/sh + +/usr/bin/ghc -pgmlc llc-3.4 -pgmlo opt-3.4 $* diff --git a/ghc-pkg b/ghc-pkg new file mode 100755 index 0000000..14e0395 --- /dev/null +++ b/ghc-pkg @@ -0,0 +1,3 @@ +#!/bin/sh + +/usr/bin/ghc-pkg $* diff --git a/ghc.spec b/ghc.spec index 44e4922..6807eca 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 26%{?dist} +Release: 27%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -33,6 +33,8 @@ Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index +Source5: ghc +Source6: ghc-pkg # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch # fedora does not allow copy libraries @@ -124,7 +126,7 @@ BuildRequires: libxslt, docbook-style-xsl BuildRequires: python %endif %ifarch armv7hl armv5tel -BuildRequires: llvm >= 3.0 +BuildRequires: llvm34 %endif %ifarch ppc64le aarch64 # for patch19 and patch21 @@ -172,7 +174,7 @@ Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 %ifarch armv7hl armv5tel -Requires: llvm >= 3.0 +Requires: llvm34 %endif %description compiler @@ -350,12 +352,19 @@ for i in $(find . -name config.guess -o -name config.sub) ; do done autoreconf %endif +%ifarch armv7hl armv5tel +export GHC=%SOURCE5 +%endif ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc + --with-gcc=%{_bindir}/gcc \ +%ifarch armv7hl armv5tel + --with-llc=%{_bindir}/llc-3.4 --with-opt=%{_bindir}/opt-3.4 \ +%endif +%{nil} # utf8 is needed when building with verbose output LANG=en_US.utf8 make %{?_smp_mflags} @@ -547,6 +556,9 @@ fi %changelog +* Mon Nov 17 2014 Jens Petersen - 7.6.3-27 +- use llvm34 instead of llvm-3.5 for arm (#1161049) + * Sat Aug 16 2014 Fedora Release Engineering - 7.6.3-26 - Rebuilt for https://fedoraproject.org/wiki/Fedora_21_22_Mass_Rebuild From 663bc535f4f8893edce114e0bcdc6aaa938dd6fa Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 18 Nov 2014 11:12:49 +0900 Subject: [PATCH 383/530] backport more changes from 7.8.3 spec to 7.6.3 spec - remove the build hack to switch from llvm to llvm34 (#1161049) - use rpm internal dependency generator with ghc.attr on F21+ - fix bash-ism in ghc-doc-index (#1146733) - do "quick" build when bootstrapping - setup LDFLAGS --- ghc | 3 --- ghc-doc-index | 2 +- ghc-pkg | 3 --- ghc.spec | 29 ++++++++++++++++++++--------- 4 files changed, 21 insertions(+), 16 deletions(-) delete mode 100755 ghc delete mode 100755 ghc-pkg diff --git a/ghc b/ghc deleted file mode 100755 index aa61e6a..0000000 --- a/ghc +++ /dev/null @@ -1,3 +0,0 @@ -#!/bin/sh - -/usr/bin/ghc -pgmlc llc-3.4 -pgmlo opt-3.4 $* diff --git a/ghc-doc-index b/ghc-doc-index index 6105d7e..a0223fa 100755 --- a/ghc-doc-index +++ b/ghc-doc-index @@ -34,5 +34,5 @@ if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; the fi if [ -f $PKGDIRCACHE.new ]; then - mv -f $PKGDIRCACHE{.new,} + mv -f $PKGDIRCACHE.new $PKGDIRCACHE fi diff --git a/ghc-pkg b/ghc-pkg deleted file mode 100755 index 14e0395..0000000 --- a/ghc-pkg +++ /dev/null @@ -1,3 +0,0 @@ -#!/bin/sh - -/usr/bin/ghc-pkg $* diff --git a/ghc.spec b/ghc.spec index 6807eca..774380c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 7.6.3 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 27%{?dist} +Release: 28%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -33,8 +33,6 @@ Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index -Source5: ghc -Source6: ghc-pkg # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch # fedora does not allow copy libraries @@ -105,7 +103,7 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -%if 0%{?fedora} >= 20 +%if 0%{?fedora} >= 19 || 0%{?rhel} >= 7 BuildRequires: ghc-rpm-macros-extra %else BuildRequires: ghc-rpm-macros @@ -198,11 +196,13 @@ documention. %global ghc_version_override %{version} +# currently only F21+ ghc-rpm-macros has ghc.attr +%if 0%{?fedora} < 21 # needs ghc_version_override for bootstrapping %global _use_internal_dependency_generator 0 %global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} %global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} - +%endif %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} @@ -328,6 +328,12 @@ BuildFlavour = perf %else BuildFlavour = perf-llvm %endif +%else +%ifnarch armv7hl armv5tel +BuildFlavour = quick-llvm +%else +BuildFlavour = quick +%endif %endif GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} %if %{defined without_haddock} @@ -343,7 +349,6 @@ BUILD_DOCBOOK_HTML = NO #EXTRA_HC_OPTS=-debug EOF -export CFLAGS="${CFLAGS:-%optflags}" # note %%configure induces cross-build due to different target/host/build platform names # --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping %ifarch ppc64le aarch64 armv7hl @@ -352,9 +357,8 @@ for i in $(find . -name config.guess -o -name config.sub) ; do done autoreconf %endif -%ifarch armv7hl armv5tel -export GHC=%SOURCE5 -%endif +export CFLAGS="${CFLAGS:-%optflags}" +export LDFLAGS="${LDFLAGS:-%__global_ldflags}" ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ @@ -556,6 +560,13 @@ fi %changelog +* Mon Nov 17 2014 Jens Petersen - 7.6.3-28 +- remove the build hack to switch from llvm to llvm34 (#1161049) +- use rpm internal dependency generator with ghc.attr on F21+ +- fix bash-ism in ghc-doc-index (#1146733) +- do "quick" build when bootstrapping +- setup LDFLAGS + * Mon Nov 17 2014 Jens Petersen - 7.6.3-27 - use llvm34 instead of llvm-3.5 for arm (#1161049) From ecce5dd44b17e47bf65c39f6e32ed2854626b5e0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 18 Nov 2014 18:19:47 +0900 Subject: [PATCH 384/530] update changelog date --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 774380c..c69b0c3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -560,7 +560,7 @@ fi %changelog -* Mon Nov 17 2014 Jens Petersen - 7.6.3-28 +* Tue Nov 18 2014 Jens Petersen - 7.6.3-28 - remove the build hack to switch from llvm to llvm34 (#1161049) - use rpm internal dependency generator with ghc.attr on F21+ - fix bash-ism in ghc-doc-index (#1146733) From 7a3899d9adc8762e8e6aa655a3d7a2c497d7500c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Jan 2015 16:55:39 +0900 Subject: [PATCH 385/530] Revert back to ghc-7.8 and update to 7.8.4 version bumps for base and Cabal This reverts commit 083d826dd60e6a529308f038d8fa6a1900729a3f. Conflicts: ghc.spec --- .gitignore | 2 + ...executable-stack-for-the-linker-note.patch | 37 +++ ghc-7.8.3-Cabal-install-PATH-warning.patch | 12 + ghc-NCG-no-execstack.patch | 32 +++ ghc-arm64.patch | 220 +++++++++++++---- ...ON.patch => ghc-armv7-VFPv3D16--NEON.patch | 8 +- ghc-cabal-unversion-docdir.patch | 26 +- ghc-ppc64el.patch | 41 ---- ghc.spec | 226 +++++++++--------- sources | 4 +- 10 files changed, 393 insertions(+), 215 deletions(-) create mode 100644 ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch create mode 100644 ghc-7.8.3-Cabal-install-PATH-warning.patch create mode 100644 ghc-NCG-no-execstack.patch rename ghc-7.6.3-armv7-VFPv3D16--NEON.patch => ghc-armv7-VFPv3D16--NEON.patch (58%) delete mode 100644 ghc-ppc64el.patch diff --git a/.gitignore b/.gitignore index 1975bde..ecf5cbb 100644 --- a/.gitignore +++ b/.gitignore @@ -14,3 +14,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.6.3/ /ghc-7.8.3-src.tar.xz /ghc-7.8.3-testsuite.tar.xz +/ghc-7.8.4-src.tar.xz +/ghc-7.8.4-testsuite.tar.xz diff --git a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch new file mode 100644 index 0000000..63583af --- /dev/null +++ b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch @@ -0,0 +1,37 @@ +From 08a38628f29df63ac842f4d083efb414f42d7bff Mon Sep 17 00:00:00 2001 +From: "Edward Z. Yang" +Date: Tue, 9 Jul 2013 00:01:43 -0700 +Subject: [PATCH] Disable executable stack for the linker note, fixing #703 + (again) + +Signed-off-by: Edward Z. Yang +--- + compiler/main/DriverPipeline.hs | 12 +++++++++++- + 1 file changed, 11 insertions(+), 1 deletion(-) + +diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs +index 67377e6..26425ae 100644 +--- a/compiler/main/DriverPipeline.hs ++++ b/compiler/main/DriverPipeline.hs +@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do + text elfSectionNote, + text "\n", + +- text "\t.ascii \"", info', text "\"\n" ] ++ text "\t.ascii \"", info', text "\"\n", ++ ++ -- ALL generated assembly must have this section to disable ++ -- executable stacks. See also ++ -- compiler/nativeGen/AsmCodeGen.lhs for another instance ++ -- where we need to do this. ++ (if platformHasGnuNonexecStack (targetPlatform dflags) ++ then text ".section .note.GNU-stack,\"\",@progbits\n" ++ else empty) ++ ++ ] + where + info' = text $ escape info + +-- +1.8.1.2 + diff --git a/ghc-7.8.3-Cabal-install-PATH-warning.patch b/ghc-7.8.3-Cabal-install-PATH-warning.patch new file mode 100644 index 0000000..e7ef6e1 --- /dev/null +++ b/ghc-7.8.3-Cabal-install-PATH-warning.patch @@ -0,0 +1,12 @@ +--- ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2014-07-10 13:34:21.000000000 +0900 ++++ ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2014-08-29 16:48:12.621694879 +0900 +@@ -148,8 +148,7 @@ + notice verbosity ("Installing executable(s) in " ++ binPref) + inPath <- isInSearchPath binPref + when (not inPath) $ +- warn verbosity ("The directory " ++ binPref +- ++ " is not in the system search path.") ++ warn verbosity ("Executable installed in " ++ binPref) + + -- install include files for all compilers - they may be needed to compile + -- haskell files (using the CPP extension) diff --git a/ghc-NCG-no-execstack.patch b/ghc-NCG-no-execstack.patch new file mode 100644 index 0000000..40b6ba6 --- /dev/null +++ b/ghc-NCG-no-execstack.patch @@ -0,0 +1,32 @@ +commit 08a38628f29df63ac842f4d083efb414f42d7bff +Author: Edward Z. Yang +Date: Tue Jul 9 00:01:43 2013 -0700 + + Disable executable stack for the linker note, fixing #703 (again) + + Signed-off-by: Edward Z. Yang + + Modified compiler/main/DriverPipeline.hs +diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs +index 67377e6..26425ae 100644 +--- a/compiler/main/DriverPipeline.hs ++++ b/compiler/main/DriverPipeline.hs +@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do + text elfSectionNote, + text "\n", + +- text "\t.ascii \"", info', text "\"\n" ] ++ text "\t.ascii \"", info', text "\"\n", ++ ++ -- ALL generated assembly must have this section to disable ++ -- executable stacks. See also ++ -- compiler/nativeGen/AsmCodeGen.lhs for another instance ++ -- where we need to do this. ++ (if platformHasGnuNonexecStack (targetPlatform dflags) ++ then text ".section .note.GNU-stack,\"\",@progbits\n" ++ else empty) ++ ++ ] + where + info' = text $ escape info + diff --git a/ghc-arm64.patch b/ghc-arm64.patch index 06a7019..7652727 100644 --- a/ghc-arm64.patch +++ b/ghc-arm64.patch @@ -1,23 +1,27 @@ -Description: Add arm64 support -Author: Karel Gardas -Author: Colin Watson +commit c29bf984dd20431cd4344e8a5c444d7a5be08389 +Author: Colin Watson +Date: Mon Apr 21 22:26:56 2014 -0500 Bug: https://ghc.haskell.org/trac/ghc/ticket/7942 -Last-Update: 2014-04-04 -Index: b/aclocal.m4 + ghc: initial AArch64 patches + + Signed-off-by: Austin Seipp + +Index: ghc-7.8.3/aclocal.m4 =================================================================== ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -173,7 +173,7 @@ +--- ghc-7.8.3.orig/aclocal.m4 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/aclocal.m4 2014-07-10 10:16:42.529187516 +0200 +@@ -197,6 +197,9 @@ GET_ARM_ISA() test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" ;; -- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) -+ aarch64|alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" ++ aarch64) ++ test -z "[$]2" || eval "[$]2=ArchARM64" ++ ;; + alpha) + test -z "[$]2" || eval "[$]2=ArchAlpha" ;; - *) -@@ -1835,6 +1835,9 @@ +@@ -1862,6 +1865,9 @@ # converts cpu from gnu to ghc naming, and assigns the result to $target_var AC_DEFUN([GHC_CONVERT_CPU],[ case "$1" in @@ -27,29 +31,161 @@ Index: b/aclocal.m4 alpha*) $2="alpha" ;; -Index: b/includes/stg/MachRegs.h +Index: ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs =================================================================== ---- a/includes/stg/MachRegs.h -+++ b/includes/stg/MachRegs.h -@@ -43,6 +43,7 @@ - #define powerpc_REGS (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) - #define sparc_REGS sparc_TARGET_ARCH - #define arm_REGS arm_TARGET_ARCH -+#define aarch64_REGS aarch64_TARGET_ARCH - #define darwin_REGS darwin_TARGET_OS - #else - #define i386_REGS i386_HOST_ARCH -@@ -50,6 +51,7 @@ - #define powerpc_REGS (powerpc_HOST_ARCH || powerpc64_HOST_ARCH || rs6000_HOST_ARCH) - #define sparc_REGS sparc_HOST_ARCH - #define arm_REGS arm_HOST_ARCH -+#define aarch64_REGS aarch64_HOST_ARCH - #define darwin_REGS darwin_HOST_OS - #endif - -@@ -461,6 +463,63 @@ +--- ghc-7.8.3.orig/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.529187516 +0200 +@@ -166,6 +166,7 @@ + ArchPPC -> nCG' (ppcNcgImpl dflags) + ArchSPARC -> nCG' (sparcNcgImpl dflags) + ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" ++ ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" + ArchPPC_64 -> panic "nativeCodeGen: No NCG for PPC 64" + ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" + ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -113,6 +113,7 @@ + ArchSPARC -> 14 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -137,6 +138,7 @@ + ArchSPARC -> 22 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -161,6 +163,7 @@ + ArchSPARC -> 11 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +@@ -185,6 +188,7 @@ + ArchSPARC -> 0 + ArchPPC_64 -> panic "trivColorable ArchPPC_64" + ArchARM _ _ _ -> panic "trivColorable ArchARM" ++ ArchARM64 -> panic "trivColorable ArchARM64" + ArchAlpha -> panic "trivColorable ArchAlpha" + ArchMipseb -> panic "trivColorable ArchMipseb" + ArchMipsel -> panic "trivColorable ArchMipsel" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -74,6 +74,7 @@ + ArchPPC -> PPC.Instr.maxSpillSlots dflags + ArchSPARC -> SPARC.Instr.maxSpillSlots dflags + ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" ++ ArchARM64 -> panic "maxSpillSlots ArchARM64" + ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" + ArchAlpha -> panic "maxSpillSlots ArchAlpha" + ArchMipseb -> panic "maxSpillSlots ArchMipseb" +Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -207,6 +207,7 @@ + ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) first_id block_live sccs + ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs + ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" ++ ArchARM64 -> panic "linearRegAlloc ArchARM64" + ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" + ArchAlpha -> panic "linearRegAlloc ArchAlpha" + ArchMipseb -> panic "linearRegAlloc ArchMipseb" +Index: ghc-7.8.3/compiler/nativeGen/TargetReg.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -54,6 +54,7 @@ + ArchSPARC -> SPARC.virtualRegSqueeze + ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" + ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" ++ ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" + ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" + ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" + ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" +@@ -70,6 +71,7 @@ + ArchSPARC -> SPARC.realRegSqueeze + ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" + ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" ++ ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" + ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" + ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" + ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" +@@ -85,6 +87,7 @@ + ArchSPARC -> SPARC.classOfRealReg + ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" + ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" ++ ArchARM64 -> panic "targetClassOfRealReg ArchARM64" + ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" + ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" + ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" +@@ -100,6 +103,7 @@ + ArchSPARC -> SPARC.mkVirtualReg + ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" + ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" ++ ArchARM64 -> panic "targetMkVirtualReg ArchARM64" + ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" + ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" + ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" +@@ -115,6 +119,7 @@ + ArchSPARC -> SPARC.regDotColor + ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" + ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" ++ ArchARM64 -> panic "targetRegDotColor ArchARM64" + ArchAlpha -> panic "targetRegDotColor ArchAlpha" + ArchMipseb -> panic "targetRegDotColor ArchMipseb" + ArchMipsel -> panic "targetRegDotColor ArchMipsel" +Index: ghc-7.8.3/compiler/utils/Platform.hs +=================================================================== +--- ghc-7.8.3.orig/compiler/utils/Platform.hs 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/compiler/utils/Platform.hs 2014-07-10 10:16:42.529187516 +0200 +@@ -52,6 +52,7 @@ + , armISAExt :: [ArmISAExt] + , armABI :: ArmABI + } ++ | ArchARM64 + | ArchAlpha + | ArchMipseb + | ArchMipsel +Index: ghc-7.8.3/includes/stg/HaskellMachRegs.h +=================================================================== +--- ghc-7.8.3.orig/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 +@@ -38,6 +38,7 @@ + #define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) + #define MACHREGS_sparc sparc_TARGET_ARCH + #define MACHREGS_arm arm_TARGET_ARCH ++#define MACHREGS_aarch64 aarch64_TARGET_ARCH + #define MACHREGS_darwin darwin_TARGET_OS - #endif /* arm */ + #endif +Index: ghc-7.8.3/includes/stg/MachRegs.h +=================================================================== +--- ghc-7.8.3.orig/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 +@@ -1,6 +1,6 @@ + /* ----------------------------------------------------------------------------- + * +- * (c) The GHC Team, 1998-2011 ++ * (c) The GHC Team, 1998-2014 + * + * Registers used in STG code. Might or might not correspond to + * actual machine registers. +@@ -531,6 +531,61 @@ + #define REG_D2 d11 + #endif +/* ----------------------------------------------------------------------------- + The ARMv8/AArch64 ABI register mapping @@ -83,7 +219,7 @@ Index: b/includes/stg/MachRegs.h + + ----------------------------------------------------------------------------- */ + -+#if aarch64_REGS ++#elif MACHREGS_aarch64 + +#define REG(x) __asm__(#x) + @@ -106,16 +242,14 @@ Index: b/includes/stg/MachRegs.h +#define REG_D1 d12 +#define REG_D2 d13 + -+#endif /* aarch64 */ -+ - #endif /* NO_REGS */ + #else - /* ----------------------------------------------------------------------------- -Index: b/rts/StgCRun.c + #error Cannot find platform to give register info for +Index: ghc-7.8.3/rts/StgCRun.c =================================================================== ---- a/rts/StgCRun.c -+++ b/rts/StgCRun.c -@@ -725,4 +725,70 @@ +--- ghc-7.8.3.orig/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 ++++ ghc-7.8.3/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 +@@ -748,4 +748,70 @@ } #endif diff --git a/ghc-7.6.3-armv7-VFPv3D16--NEON.patch b/ghc-armv7-VFPv3D16--NEON.patch similarity index 58% rename from ghc-7.6.3-armv7-VFPv3D16--NEON.patch rename to ghc-armv7-VFPv3D16--NEON.patch index 6412ff5..e51a353 100644 --- a/ghc-7.6.3-armv7-VFPv3D16--NEON.patch +++ b/ghc-armv7-VFPv3D16--NEON.patch @@ -1,7 +1,7 @@ ---- ghc-7.6.3/aclocal.m4~ 2013-04-19 06:22:46.000000000 +0900 -+++ ghc-7.6.3/aclocal.m4 2014-07-15 18:22:12.308929288 +0900 -@@ -349,7 +349,7 @@ - ], +--- ghc-7.8.3/aclocal.m4~ 2014-07-10 13:27:16.000000000 +0900 ++++ ghc-7.8.3/aclocal.m4 2014-11-05 12:19:08.530044128 +0900 +@@ -408,7 +408,7 @@ + )], [changequote(, )dnl ARM_ISA=ARMv7 - ARM_ISA_EXT="[VFPv3,NEON]" diff --git a/ghc-cabal-unversion-docdir.patch b/ghc-cabal-unversion-docdir.patch index 0aefeb5..9d0b026 100644 --- a/ghc-cabal-unversion-docdir.patch +++ b/ghc-cabal-unversion-docdir.patch @@ -1,13 +1,13 @@ ---- ghc-7.6.3/utils/ghc-cabal/Main.hs~ 2013-04-19 06:22:47.000000000 +0900 -+++ ghc-7.6.3/utils/ghc-cabal/Main.hs 2013-10-29 12:35:18.916340631 +0900 -@@ -180,8 +180,8 @@ - libsubdir = toPathTemplate "$pkgid", - docdir = toPathTemplate $ - if relocatableBuild -- then "$topdir/../doc/html/libraries/$pkgid" -- else (myDocdir "$pkgid"), -+ then "$topdir/../doc/html/libraries/$pkg" -+ else (myDocdir "$pkg"), - htmldir = toPathTemplate "$docdir" - } - progs = withPrograms lbi +--- ghc-7.8/utils/ghc-cabal/Main.hs~ 2013-08-28 08:06:37.000000000 +0900 ++++ ghc-7.8/utils/ghc-cabal/Main.hs 2013-09-03 17:51:22.800653817 +0900 +@@ -251,8 +251,8 @@ + libsubdir = toPathTemplate "$pkgid", + docdir = toPathTemplate $ + if relocatableBuild +- then "$topdir/../doc/html/libraries/$pkgid" +- else (myDocdir "$pkgid"), ++ then "$topdir/../doc/html/libraries/$pkg" ++ else (myDocdir "$pkg"), + htmldir = toPathTemplate "$docdir" + } + diff --git a/ghc-ppc64el.patch b/ghc-ppc64el.patch deleted file mode 100644 index 9841054..0000000 --- a/ghc-ppc64el.patch +++ /dev/null @@ -1,41 +0,0 @@ -Description: Add ppc64el support -Author: Colin Watson -Bug: https://ghc.haskell.org/trac/ghc/ticket/8965 -Last-Update: 2014-04-12 - -Index: b/aclocal.m4 -=================================================================== ---- a/aclocal.m4 -+++ b/aclocal.m4 -@@ -173,7 +173,7 @@ - GET_ARM_ISA() - test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" - ;; -- alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|rs6000|s390|s390x|sparc64|vax) -+ alpha|mips|mipseb|mipsel|hppa|hppa1_1|ia64|m68k|powerpc64le|rs6000|s390|s390x|sparc64|vax) - test -z "[$]2" || eval "[$]2=ArchUnknown" - ;; - *) -@@ -1868,6 +1868,9 @@ - mips*) - $2="mips" - ;; -+ powerpc64le*) -+ $2="powerpc64le" -+ ;; - powerpc64*) - $2="powerpc64" - ;; -Index: b/includes/Stg.h -=================================================================== ---- a/includes/Stg.h -+++ b/includes/Stg.h -@@ -213,7 +213,7 @@ - #define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) - #define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) - #define FN_(f) StgFunPtr f(void) --#define EF_(f) extern StgFunPtr f(void) -+#define EF_(f) extern StgFunPtr f() - - /* ----------------------------------------------------------------------------- - Tail calls diff --git a/ghc.spec b/ghc.spec index c69b0c3..47a4059 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,96 +1,93 @@ -# Shared haskell libraries are supported for x86* archs -# (disabled for other archs in ghc-rpm-macros) - # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%global without_testsuite 1 -### either: -#%%{?ghc_bootstrap} -### or for shared libs: -#%%{?ghc_test} +%global ghc_bootstrapping 1 +%global without_testsuite 1 +%global without_prof 1 +%if 0%{?fedora} >= 22 +%{?ghc_bootstrap} +%else +%{?ghc_test} +%endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock +# make sure to turn on shared libs for all arches +# (for building on releases earlier than F22) +%if %{defined ghc_without_shared} +%undefine ghc_without_shared +%endif + %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.6.3 +Version: 7.8.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 28%{?dist} +# xhtml moved from haskell-platform to ghc-7.8.3 +Release: 39%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport URL: http://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.bz2 +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.bz2 +Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch -# fedora does not allow copy libraries -Patch4: ghc-use-system-libffi.patch -# fix dynamic linking of executables using Template Haskell -Patch9: Cabal-fix-dynamic-exec-for-TH.patch # add libffi include dir to ghc wrapper for archs using gcc/llc -Patch10: ghc-wrapper-libffi-include.patch -# disable building HS*.o libs for ghci -Patch12: ghc-7.4.2-Cabal-disable-ghci-libs.patch -# fix compilation with llvm-3.3 -Patch13: ghc-llvmCodeGen-empty-array.patch +#Patch10: ghc-wrapper-libffi-include.patch # stop warnings about unsupported version of llvm -Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch -# fix hang on ppc64 and s390x (upstream in 7.8) -Patch15: ghc-64bit-bigendian-rts-hang-989593.patch +# NB: value affects ABI hash of libHSghc! +# will probably be needed again for llvm-3.5 +#Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch -# fix libffi segfaults on 32bit (upstream in 7.8) -Patch17: ghc-7.6.3-rts-Adjustor-32bit-segfault.patch -# add .note.GNU-stack to assembly output to avoid execstack (#973512) -# (disabled for now since it changes libghc ABI and fix only works for i686) -#Patch18: ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch -# changes for ppc64le committed upstream for 7.8.3 -# (https://ghc.haskell.org/trac/ghc/ticket/8965) -Patch19: ghc-ppc64el.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch Patch21: ghc-arm64.patch -Patch22: ghc-7.6.3-armv7-VFPv3D16--NEON.patch +Patch22: ghc-armv7-VFPv3D16--NEON.patch +Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch -%global Cabal_ver 1.16.0 -%global array_ver 0.4.0.1 -%global base_ver 4.6.0.1 +%global Cabal_ver 1.18.1.5 +%global array_ver 0.5.0.0 +%global base_ver 4.7.0.2 %global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.5.1.1 -%global bytestring_ver 0.10.0.2 -%global containers_ver 0.5.0.0 -%global deepseq_ver 1.3.0.1 -%global directory_ver 1.2.0.1 -%global filepath_ver 1.3.0.1 -%global ghc_prim_ver 0.3.0.0 -%global haskell2010_ver 1.1.1.0 -%global haskell98_ver 2.0.0.2 -%global hoopl_ver 3.9.0.0 -%global hpc_ver 0.6.0.0 -%global integer_gmp_ver 0.5.0.0 -%global old_locale_ver 1.0.0.5 -%global old_time_ver 1.1.0.1 -%global pretty_ver 1.1.1.0 -%global process_ver 1.1.0.2 -%global template_haskell_ver 2.8.0.0 -%global time_ver 1.4.0.1 -%global unix_ver 2.6.0.1 +%global binary_ver 0.7.1.0 +%global bytestring_ver 0.10.4.0 +%global containers_ver 0.5.5.1 +%global deepseq_ver 1.3.0.2 +%global directory_ver 1.2.1.0 +%global filepath_ver 1.3.0.2 +%global ghc_prim_ver 0.3.1.0 +%global haskeline_ver 0.7.1.2 +%global haskell2010_ver 1.1.2.0 +%global haskell98_ver 2.0.0.3 +%global hoopl_ver 3.10.0.1 +%global hpc_ver 0.6.0.1 +%global integer_gmp_ver 0.5.1.0 +%global old_locale_ver 1.0.0.6 +%global old_time_ver 1.1.0.2 +%global pretty_ver 1.1.1.1 +%global process_ver 1.2.0.0 +%global template_haskell_ver 2.9.0.0 +%global terminfo_ver 0.4.0.0 +%global time_ver 1.4.2 +%global transformers_ver 0.3.0.0 +%global unix_ver 2.7.0.1 +%global xhtml_ver 3000.2.1 + # fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc alpha sparcv9 ppc64 armv7hl armv5tel s390 s390x +# %{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 +# and retired arches: alpha sparcv9 armv5tel # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros ExcludeArch: sparc64 Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 @@ -103,11 +100,12 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -%if 0%{?fedora} >= 19 || 0%{?rhel} >= 7 +%if 0%{?fedora} >= 20 || 0%{?rhel} >= 7 BuildRequires: ghc-rpm-macros-extra %else BuildRequires: ghc-rpm-macros %endif +BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel @@ -116,9 +114,9 @@ BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel BuildRequires: gmp-devel BuildRequires: libffi-devel -# for internal terminfo +# for terminfo BuildRequires: ncurses-devel -# for manpage and docs +# for man and docs BuildRequires: libxslt, docbook-style-xsl %if %{undefined without_testsuite} BuildRequires: python @@ -126,11 +124,7 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm34 %endif -%ifarch ppc64le aarch64 -# for patch19 and patch21 -BuildRequires: autoconf -%endif -%ifarch armv7hl +%ifarch armv7hl aarch64 # patch22 BuildRequires: autoconf, automake %endif @@ -194,6 +188,7 @@ The package provides a cronjob for re-indexing installed library development documention. %endif +# ghclibdir also needs ghc_version_override for bootstrapping (ghc-deps.sh) %global ghc_version_override %{version} # currently only F21+ ghc-rpm-macros has ghc.attr @@ -220,6 +215,7 @@ documention. # in ghc not ghc-libraries: %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes +%ghc_lib_subpackage haskeline %{haskeline_ver} %ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver} %ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver} %ghc_lib_subpackage hoopl %{hoopl_ver} @@ -231,8 +227,11 @@ documention. %ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} %undefine ghc_pkg_obsoletes %ghc_lib_subpackage template-haskell %{template_haskell_ver} +%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo %{terminfo_ver} %ghc_lib_subpackage time %{time_ver} +%ghc_lib_subpackage transformers %{transformers_ver} %ghc_lib_subpackage unix %{unix_ver} +%ghc_lib_subpackage xhtml %{xhtml_ver} %endif %global version %{ghc_version_override} @@ -260,44 +259,21 @@ except the ghc library, which is installed by the toplevel ghc metapackage. # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig -# make sure we don't use these -rm -r ghc-tarballs/{mingw*,perl} -# use system libffi -%patch4 -p1 -b .libffi -rm -r ghc-tarballs/libffi -mkdir -p rts/dist/build -ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build - -%patch9 -p1 -b .orig +rm -r libffi-tarballs %ifnarch %{ix86} x86_64 -%patch10 -p1 -b .10-ffi +#%%patch10 -p1 -b .10-ffi %endif -%patch12 -p1 -b .orig - -%patch13 -p1 -b .orig - %ifarch armv7hl armv5tel -%patch14 -p1 -b .orig -%endif - -%ifarch ppc64 s390x -%patch15 -p1 -b .orig +#%%patch14 -p1 -b .orig %endif +# unversion pkgdoc htmldir %if 0%{?fedora} >= 21 %patch16 -p1 -b .orig %endif -%patch17 -p0 -b .orig - -#%%patch18 -p1 -b .orig - -%ifarch ppc64le -%patch19 -p1 -b .orig -%endif - %patch20 -p1 -b .orig %ifarch aarch64 @@ -308,6 +284,7 @@ ln -s $(pkg-config --variable=includedir libffi)/*.h rts/dist/build %patch22 -p1 -b .orig %endif +%patch23 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -335,7 +312,7 @@ BuildFlavour = quick-llvm BuildFlavour = quick %endif %endif -GhcLibWays = v %{!?ghc_without_shared:dyn} %{!?without_prof:p} +GhcLibWays = v dyn %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif @@ -349,29 +326,32 @@ BUILD_DOCBOOK_HTML = NO #EXTRA_HC_OPTS=-debug EOF -# note %%configure induces cross-build due to different target/host/build platform names -# --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping -%ifarch ppc64le aarch64 armv7hl +%ifarch aarch64 for i in $(find . -name config.guess -o -name config.sub) ; do [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i done +%endif +%ifarch aarch64 armv7hl autoreconf %endif export CFLAGS="${CFLAGS:-%optflags}" export LDFLAGS="${LDFLAGS:-%__global_ldflags}" +# * %%configure induces cross-build due to different target/host/build platform names +# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc \ + --with-gcc=%{_bindir}/gcc --with-system-libffi \ %ifarch armv7hl armv5tel --with-llc=%{_bindir}/llc-3.4 --with-opt=%{_bindir}/opt-3.4 \ %endif %{nil} -# utf8 is needed when building with verbose output -LANG=en_US.utf8 make %{?_smp_mflags} +# avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" +export LANG=en_US.utf8 +make %{?_smp_mflags} %install @@ -403,11 +383,13 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist bin-package-db ghc # add rts libs -%if %{undefined ghc_without_shared} -ls %{buildroot}%{ghclibdir}/libHS*.so >> ghc-base.files +echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files +ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files + sed -i -e "s|^%{buildroot}||g" ghc-base.files -%endif -ls -d %{buildroot}%{ghclibdir}/libHS*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files + +ls -d %{buildroot}%{ghclibdir}/rts-1.0/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files + sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files # these are handled as alternatives @@ -434,8 +416,12 @@ sh %{gen_contents_index} --intree --verbose cd .. %endif +# we package the library license files separately +find %{buildroot}%ghclibdocdir -name LICENSE -exec rm '{}' ';' + %check +export LANG=en_US.utf8 # stolen from ghc6/debian/rules: GHC=inplace/bin/ghc-stage2 # Do some very simple tests that the compiler actually works @@ -451,12 +437,10 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -O2 [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if %{undefined ghc_without_shared} echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%endif %if %{undefined without_testsuite} make test %endif @@ -490,13 +474,15 @@ fi %files %files compiler -%doc ANNOUNCE HACKING LICENSE README +%doc ANNOUNCE LICENSE %{_bindir}/ghc %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} +%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} +%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -504,18 +490,22 @@ fi %{_bindir}/runghc* %ghost %{_bindir}/runhaskell %{_bindir}/runhaskell-ghc -%{ghclibdir}/ghc -%{ghclibdir}/ghc-pkg -# unknown ("unregisterized") archs +%dir %{ghclibdir}/bin +%{ghclibdir}/bin/ghc +%{ghclibdir}/bin/ghc-pkg +%{ghclibdir}/bin/hpc +%{ghclibdir}/bin/hsc2hs +%{ghclibdir}/bin/runghc +# unknown (unregisterized) archs %ifnarch ppc64 s390 s390x ppc64le aarch64 %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt -%{ghclibdir}/hsc2hs +%{ghclibdir}/mkGmpDerivedConstants %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache -%{ghclibdir}/runghc +%{ghclibdir}/platformConstants %{ghclibdir}/settings %{ghclibdir}/template-hsc.h %{ghclibdir}/unlit @@ -526,7 +516,7 @@ fi %{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} -%{ghclibdir}/haddock +%{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex %if %{undefined without_manual} @@ -560,6 +550,18 @@ fi %changelog +* Sat Jan 17 2015 Jens Petersen - 7.8.4-39 +- update to 7.8.4 +- bump release over haskell-platform xhtml +- https://www.haskell.org/ghc/docs/7.8.4/html/users_guide/release-7-8-1.html +- https://www.haskell.org/ghc/docs/7.8.4/html/users_guide/release-7-8-2.html +- https://www.haskell.org/ghc/docs/7.8.4/html/users_guide/release-7-8-3.html +- https://www.haskell.org/ghc/docs/7.8.4/html/users_guide/release-7-8-4.html +- bootstrap build +- provides haskeline, terminfo and xhtml libraries +- shared libraries on all archs +- bindir/ghci only on ghc_arches_with_ghci + * Tue Nov 18 2014 Jens Petersen - 7.6.3-28 - remove the build hack to switch from llvm to llvm34 (#1161049) - use rpm internal dependency generator with ghc.attr on F21+ diff --git a/sources b/sources index 40df58f..dff0a54 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -986d1f90ca30d60f7b2820d75c6b8ea7 ghc-7.6.3-src.tar.bz2 -66aa6177a31cc4b9d7eeb55cb1514918 ghc-7.6.3-testsuite.tar.bz2 +91f74cf9d813603cc3145528db4bbead ghc-7.8.4-src.tar.xz +3cc3353d99518be7e7b2d78ebd5460b5 ghc-7.8.4-testsuite.tar.xz From 30d039255ab0b73295bdd47beadc1aacd976fd7f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 17 Jan 2015 23:12:47 +0900 Subject: [PATCH 386/530] use ld.gold on ARMv7 see https://ghc.haskell.org/trac/ghc/ticket/8976 for workaround patches posted upstream by nomeata remove some old leftover patches (fedpkg unused-patches) --- ghc-64bit-bigendian-rts-hang-989593.patch | 11 --- ghc-7.4.2-Cabal-disable-ghci-libs.patch | 13 ---- ...executable-stack-for-the-linker-note.patch | 37 --------- ...6.3-LlvmCodeGen-llvm-version-warning.patch | 11 --- ghc-7.6.3-rts-Adjustor-32bit-segfault.patch | 11 --- ghc-7.8-arm7-use-ld-gold-8976.patch | 17 ++++ ...-arm7_saner-linker-opt-handling-9873.patch | 78 +++++++++++++++++++ ghc-NCG-no-execstack.patch | 32 -------- ghc-llvmCodeGen-empty-array.patch | 46 ----------- ghc.spec | 16 ++-- 10 files changed, 102 insertions(+), 170 deletions(-) delete mode 100644 ghc-64bit-bigendian-rts-hang-989593.patch delete mode 100644 ghc-7.4.2-Cabal-disable-ghci-libs.patch delete mode 100644 ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch delete mode 100644 ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch delete mode 100644 ghc-7.6.3-rts-Adjustor-32bit-segfault.patch create mode 100644 ghc-7.8-arm7-use-ld-gold-8976.patch create mode 100644 ghc-7.8-arm7_saner-linker-opt-handling-9873.patch delete mode 100644 ghc-NCG-no-execstack.patch delete mode 100644 ghc-llvmCodeGen-empty-array.patch diff --git a/ghc-64bit-bigendian-rts-hang-989593.patch b/ghc-64bit-bigendian-rts-hang-989593.patch deleted file mode 100644 index 279e666..0000000 --- a/ghc-64bit-bigendian-rts-hang-989593.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- a/rts/STM.c -+++ b/rts/STM.c -@@ -927,7 +927,7 @@ void stmPreGCHook (Capability *cap) { - static volatile StgInt64 max_commits = 0; - - #if defined(THREADED_RTS) --static volatile StgBool token_locked = FALSE; -+static volatile StgWord token_locked = FALSE; - - static void getTokenBatch(Capability *cap) { - while (cas((void *)&token_locked, FALSE, TRUE) == TRUE) { /* nothing */ } diff --git a/ghc-7.4.2-Cabal-disable-ghci-libs.patch b/ghc-7.4.2-Cabal-disable-ghci-libs.patch deleted file mode 100644 index cdefe0d..0000000 --- a/ghc-7.4.2-Cabal-disable-ghci-libs.patch +++ /dev/null @@ -1,13 +0,0 @@ ---- ghc-7.4.2/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs~ 2012-06-07 02:10:40.000000000 +0900 -+++ ghc-7.4.2/libraries/Cabal/Cabal/Distribution/Simple/Setup.hs 2012-08-24 20:33:00.032123967 +0900 -@@ -313,7 +313,7 @@ - configDistPref = Flag defaultDistPref, - configVerbosity = Flag normal, - configUserInstall = Flag False, --TODO: reverse this -- configGHCiLib = Flag True, -+ configGHCiLib = Flag False, - configSplitObjs = Flag False, -- takes longer, so turn off by default - configStripExes = Flag True, - configTests = Flag False, - -Diff finished. Fri Aug 24 20:33:10 2012 diff --git a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch b/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch deleted file mode 100644 index 63583af..0000000 --- a/ghc-7.6-driver-Disable-executable-stack-for-the-linker-note.patch +++ /dev/null @@ -1,37 +0,0 @@ -From 08a38628f29df63ac842f4d083efb414f42d7bff Mon Sep 17 00:00:00 2001 -From: "Edward Z. Yang" -Date: Tue, 9 Jul 2013 00:01:43 -0700 -Subject: [PATCH] Disable executable stack for the linker note, fixing #703 - (again) - -Signed-off-by: Edward Z. Yang ---- - compiler/main/DriverPipeline.hs | 12 +++++++++++- - 1 file changed, 11 insertions(+), 1 deletion(-) - -diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs -index 67377e6..26425ae 100644 ---- a/compiler/main/DriverPipeline.hs -+++ b/compiler/main/DriverPipeline.hs -@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do - text elfSectionNote, - text "\n", - -- text "\t.ascii \"", info', text "\"\n" ] -+ text "\t.ascii \"", info', text "\"\n", -+ -+ -- ALL generated assembly must have this section to disable -+ -- executable stacks. See also -+ -- compiler/nativeGen/AsmCodeGen.lhs for another instance -+ -- where we need to do this. -+ (if platformHasGnuNonexecStack (targetPlatform dflags) -+ then text ".section .note.GNU-stack,\"\",@progbits\n" -+ else empty) -+ -+ ] - where - info' = text $ escape info - --- -1.8.1.2 - diff --git a/ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch b/ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch deleted file mode 100644 index ef274e6..0000000 --- a/ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-7.6.3/compiler/llvmGen/LlvmCodeGen/Base.hs~ 2013-04-19 06:22:46.000000000 +0900 -+++ ghc-7.6.3/compiler/llvmGen/LlvmCodeGen/Base.hs 2013-07-24 17:05:06.491900335 +0900 -@@ -151,7 +151,7 @@ - minSupportLlvmVersion = 28 - - maxSupportLlvmVersion :: LlvmVersion --maxSupportLlvmVersion = 31 -+maxSupportLlvmVersion = 34 - - -- ---------------------------------------------------------------------------- - -- * Environment Handling diff --git a/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch b/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch deleted file mode 100644 index ca608e7..0000000 --- a/ghc-7.6.3-rts-Adjustor-32bit-segfault.patch +++ /dev/null @@ -1,11 +0,0 @@ -Index: rts/Adjustor.c -=================================================================== ---- rts/Adjustor.c (revision c2870706b29c24ac86ae2a9e2359dd1e4af71ac8) -+++ rts/Adjustor.c (revision 27cf625ab871f34434d9fe86cecf85a31f73f0e5) -@@ -390,5 +390,5 @@ - - adjustorStub->call[0] = 0xe8; -- *(long*)&adjustorStub->call[1] = ((char*)&adjustorCode) - ((char*)adjustorStub + 5); -+ *(long*)&adjustorStub->call[1] = ((char*)&adjustorCode) - ((char*)code + 5); - adjustorStub->hptr = hptr; - adjustorStub->wptr = wptr; diff --git a/ghc-7.8-arm7-use-ld-gold-8976.patch b/ghc-7.8-arm7-use-ld-gold-8976.patch new file mode 100644 index 0000000..6852db5 --- /dev/null +++ b/ghc-7.8-arm7-use-ld-gold-8976.patch @@ -0,0 +1,17 @@ +Patch by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 + +Index: ghc-7.8.3.20141119/aclocal.m4 +=================================================================== +--- ghc-7.8.3.20141119.orig/aclocal.m4 2014-12-08 18:49:28.207171714 +0100 ++++ ghc-7.8.3.20141119/aclocal.m4 2014-12-08 19:03:06.815522917 +0100 +@@ -553,6 +553,10 @@ + $3="$$3 -D_HPUX_SOURCE" + $5="$$5 -D_HPUX_SOURCE" + ;; ++ arm*) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; + esac + + # If gcc knows about the stack protector, turn it off. diff --git a/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch b/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch new file mode 100644 index 0000000..c44a21f --- /dev/null +++ b/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch @@ -0,0 +1,78 @@ +On ARM, we want to make sure that GHC uses the gold linker. + +In order to achieve that, we need to get `-fuse-ld=gold` into +SettingsCCompilerLinkFlags in the settings. + +This field is filled with only CONF_GCC_LINKER_OPTS_STAGE2. So we want that +flag to show up there. + +But this variable is used in a few other cases (LDFLAGS, options to hsc2hs) +where -fuse-ld=gold caused problems. +(These problems were not investigated. Maybe _they_ could be solved?) + +So as a work-around we remove any other use of CONF_GCC_LINKER_OPTS_STAGE2. + + +Index: ghc-7.8.3.20141119/libffi/ghc.mk +=================================================================== +--- ghc-7.8.3.20141119.orig/libffi/ghc.mk 2014-04-07 20:26:08.000000000 +0200 ++++ ghc-7.8.3.20141119/libffi/ghc.mk 2014-12-08 18:57:03.392339809 +0100 +@@ -88,7 +88,7 @@ + NM=$(NM) \ + RANLIB=$(REAL_RANLIB_CMD) \ + CFLAGS="$(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE1) -w" \ +- LDFLAGS="$(SRC_LD_OPTS) $(CONF_GCC_LINKER_OPTS_STAGE1) -w" \ ++ LDFLAGS="$(SRC_LD_OPTS) -w" \ + "$(SHELL)" ./configure \ + --prefix=$(TOP)/libffi/build/inst \ + --libdir=$(TOP)/libffi/build/inst/lib \ +Index: ghc-7.8.3.20141119/mk/config.mk.in +=================================================================== +--- ghc-7.8.3.20141119.orig/mk/config.mk.in 2014-12-08 18:49:28.215171926 +0100 ++++ ghc-7.8.3.20141119/mk/config.mk.in 2014-12-08 18:57:20.637055726 +0100 +@@ -570,7 +570,6 @@ + # $1 = stage + SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) + SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) +-SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) + endef + $(eval $(call set_stage_HSC2HS_OPTS,0)) + $(eval $(call set_stage_HSC2HS_OPTS,1)) +Index: ghc-7.8.3.20141119/rules/build-package-data.mk +=================================================================== +--- ghc-7.8.3.20141119.orig/rules/build-package-data.mk 2014-04-14 14:38:12.000000000 +0200 ++++ ghc-7.8.3.20141119/rules/build-package-data.mk 2014-12-08 18:57:49.366250332 +0100 +@@ -50,7 +50,7 @@ + # for a feature it may not generate warning-free C code, and thus may + # think that the feature doesn't exist if -Werror is on. + $1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) +-$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) ++$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) + $1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) + + $1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" +Index: ghc-7.8.3.20141119/rules/distdir-opts.mk +=================================================================== +--- ghc-7.8.3.20141119.orig/rules/distdir-opts.mk 2014-04-07 20:26:08.000000000 +0200 ++++ ghc-7.8.3.20141119/rules/distdir-opts.mk 2014-12-08 18:58:18.435461083 +0100 +@@ -64,7 +64,6 @@ + endif + + $1_$2_DIST_LD_OPTS = \ +- $$(CONF_GCC_LINKER_OPTS_STAGE$3) \ + $$(SRC_LD_OPTS) \ + $$($1_LD_OPTS) \ + $$($1_$2_LD_OPTS) \ +Index: ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk +=================================================================== +--- ghc-7.8.3.20141119.orig/utils/hsc2hs/ghc.mk 2014-04-07 20:26:15.000000000 +0200 ++++ ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk 2014-12-08 18:57:07.848524715 +0100 +@@ -27,7 +27,7 @@ + # system uses it for all stages and passes the right options for each stage + # on the command line + define utils/hsc2hs_dist-install_SHELL_WRAPPER_EXTRA +-echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)" ++echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1))"' >> "$(WRAPPER)" + endef + + ifneq "$(BINDIST)" "YES" diff --git a/ghc-NCG-no-execstack.patch b/ghc-NCG-no-execstack.patch deleted file mode 100644 index 40b6ba6..0000000 --- a/ghc-NCG-no-execstack.patch +++ /dev/null @@ -1,32 +0,0 @@ -commit 08a38628f29df63ac842f4d083efb414f42d7bff -Author: Edward Z. Yang -Date: Tue Jul 9 00:01:43 2013 -0700 - - Disable executable stack for the linker note, fixing #703 (again) - - Signed-off-by: Edward Z. Yang - - Modified compiler/main/DriverPipeline.hs -diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs -index 67377e6..26425ae 100644 ---- a/compiler/main/DriverPipeline.hs -+++ b/compiler/main/DriverPipeline.hs -@@ -1640,7 +1640,17 @@ mkNoteObjsToLinkIntoBinary dflags dep_packages = do - text elfSectionNote, - text "\n", - -- text "\t.ascii \"", info', text "\"\n" ] -+ text "\t.ascii \"", info', text "\"\n", -+ -+ -- ALL generated assembly must have this section to disable -+ -- executable stacks. See also -+ -- compiler/nativeGen/AsmCodeGen.lhs for another instance -+ -- where we need to do this. -+ (if platformHasGnuNonexecStack (targetPlatform dflags) -+ then text ".section .note.GNU-stack,\"\",@progbits\n" -+ else empty) -+ -+ ] - where - info' = text $ escape info - diff --git a/ghc-llvmCodeGen-empty-array.patch b/ghc-llvmCodeGen-empty-array.patch deleted file mode 100644 index 5dc3e96..0000000 --- a/ghc-llvmCodeGen-empty-array.patch +++ /dev/null @@ -1,46 +0,0 @@ -commit db9b63105a541e4ad3f9c55e2cfadf716445ab87 -Author: Geoffrey Mainland -Date: Wed Jun 12 14:31:49 2013 +0100 - - Avoid generating empty llvm.used definitions. - - LLVM 3.3rc3 complains when the llvm.used global is an empty array, so don't - define llvm.used at all when it would be empty. - - Modified compiler/llvmGen/LlvmCodeGen.hs -diff --git a/compiler/llvmGen/LlvmCodeGen.hs b/compiler/llvmGen/LlvmCodeGen.hs -index a157a25..4f2bded 100644 ---- a/compiler/llvmGen/LlvmCodeGen.hs -+++ b/compiler/llvmGen/LlvmCodeGen.hs -@@ -117,19 +117,19 @@ cmmProcLlvmGens :: DynFlags -> BufHandle -> UniqSupply -> LlvmEnv -> [RawCmmDecl - -> [[LlvmVar]] -- ^ info tables that need to be marked as 'used' - -> IO () - --cmmProcLlvmGens _ _ _ _ [] _ [] -- = return () -- - cmmProcLlvmGens dflags h _ _ [] _ ivars -- = let ivars' = concat ivars -- cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr -- ty = (LMArray (length ivars') i8Ptr) -- usedArray = LMStaticArray (map cast ivars') ty -- lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending -- (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray) -- in Prt.bufLeftRender h $ {-# SCC "llvm_used_ppr" #-} -- withPprStyleDoc dflags (mkCodeStyle CStyle) $ -- pprLlvmData ([lmUsed], []) -+ | null ivars' = return () -+ | otherwise = Prt.bufLeftRender h $ -+ {-# SCC "llvm_used_ppr" #-} -+ withPprStyleDoc dflags (mkCodeStyle CStyle) $ -+ pprLlvmData ([lmUsed], []) -+ where -+ ivars' = concat ivars -+ cast x = LMBitc (LMStaticPointer (pVarLift x)) i8Ptr -+ ty = (LMArray (length ivars') i8Ptr) -+ usedArray = LMStaticArray (map cast ivars') ty -+ lmUsed = (LMGlobalVar (fsLit "llvm.used") ty Appending -+ (Just $ fsLit "llvm.metadata") Nothing False, Just usedArray) - - cmmProcLlvmGens dflags h us env ((CmmData _ _) : cmms) count ivars - = cmmProcLlvmGens dflags h us env cmms count ivars diff --git a/ghc.spec b/ghc.spec index 47a4059..c5e2041 100644 --- a/ghc.spec +++ b/ghc.spec @@ -43,10 +43,6 @@ Source4: ghc-doc-index Patch1: ghc-gen_contents_index-haddock-path.patch # add libffi include dir to ghc wrapper for archs using gcc/llc #Patch10: ghc-wrapper-libffi-include.patch -# stop warnings about unsupported version of llvm -# NB: value affects ABI hash of libHSghc! -# will probably be needed again for llvm-3.5 -#Patch14: ghc-7.6.3-LlvmCodeGen-llvm-version-warning.patch # unversion library html docdirs Patch16: ghc-cabal-unversion-docdir.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" @@ -55,6 +51,8 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch Patch21: ghc-arm64.patch Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch +Patch24: ghc-7.8-arm7-use-ld-gold-8976.patch +Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch %global Cabal_ver 1.18.1.5 %global array_ver 0.5.0.0 @@ -125,7 +123,7 @@ BuildRequires: python BuildRequires: llvm34 %endif %ifarch armv7hl aarch64 -# patch22 +# patch22 and patch24 BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} @@ -265,10 +263,6 @@ rm -r libffi-tarballs #%%patch10 -p1 -b .10-ffi %endif -%ifarch armv7hl armv5tel -#%%patch14 -p1 -b .orig -%endif - # unversion pkgdoc htmldir %if 0%{?fedora} >= 21 %patch16 -p1 -b .orig @@ -282,6 +276,8 @@ rm -r libffi-tarballs %ifarch armv7hl %patch22 -p1 -b .orig +%patch24 -p1 -b .24~ +%patch25 -p1 -b .25~ %endif %patch23 -p1 -b .orig @@ -561,6 +557,8 @@ fi - provides haskeline, terminfo and xhtml libraries - shared libraries on all archs - bindir/ghci only on ghc_arches_with_ghci +- use ld.gold on ARMv7 (see https://ghc.haskell.org/trac/ghc/ticket/8976) + [thanks to nomeata for workaround patches posted upstream] * Tue Nov 18 2014 Jens Petersen - 7.6.3-28 - remove the build hack to switch from llvm to llvm34 (#1161049) From 8d155fe9a593f84874dea26ddc8d8d43e7784b5e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 18 Jan 2015 15:58:37 +0900 Subject: [PATCH 387/530] production build --- ghc.spec | 23 +++++++++++++---------- 1 file changed, 13 insertions(+), 10 deletions(-) diff --git a/ghc.spec b/ghc.spec index c5e2041..51cf5f9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,12 @@ # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 -%global without_testsuite 1 -%global without_prof 1 -%if 0%{?fedora} >= 22 -%{?ghc_bootstrap} -%else -%{?ghc_test} -%endif +#%%global ghc_bootstrapping 1 +#%%global without_testsuite 1 +#%%global without_prof 1 +#%%if 0%{?fedora} >= 22 +#%%{?ghc_bootstrap} +#%%else +#%%{?ghc_test} +#%%endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock @@ -28,7 +28,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 39%{?dist} +Release: 40%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -546,6 +546,9 @@ fi %changelog +* Sun Jan 18 2015 Jens Petersen - 7.8.4-40 +- production build + * Sat Jan 17 2015 Jens Petersen - 7.8.4-39 - update to 7.8.4 - bump release over haskell-platform xhtml @@ -558,7 +561,7 @@ fi - shared libraries on all archs - bindir/ghci only on ghc_arches_with_ghci - use ld.gold on ARMv7 (see https://ghc.haskell.org/trac/ghc/ticket/8976) - [thanks to nomeata for workaround patches posted upstream] + [thanks to Joachim Breitner for workaround patches posted upstream] * Tue Nov 18 2014 Jens Petersen - 7.6.3-28 - remove the build hack to switch from llvm to llvm34 (#1161049) From 49bc24eee0f866c881b4ab056c2de329ce737ba5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 18 Jan 2015 22:51:39 +0900 Subject: [PATCH 388/530] drop unversioned htmldir patch remove two old patches --- Cabal-fix-dynamic-exec-for-TH.patch | 23 --------- ghc-cabal-unversion-docdir.patch | 13 ----- ghc-use-system-libffi.patch | 73 ----------------------------- ghc.spec | 8 +--- 4 files changed, 1 insertion(+), 116 deletions(-) delete mode 100644 Cabal-fix-dynamic-exec-for-TH.patch delete mode 100644 ghc-cabal-unversion-docdir.patch delete mode 100644 ghc-use-system-libffi.patch diff --git a/Cabal-fix-dynamic-exec-for-TH.patch b/Cabal-fix-dynamic-exec-for-TH.patch deleted file mode 100644 index fb95f83..0000000 --- a/Cabal-fix-dynamic-exec-for-TH.patch +++ /dev/null @@ -1,23 +0,0 @@ ---- ghc-7.6.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs~ 2013-04-19 06:32:04.000000000 +0900 -+++ ghc-7.6.3/libraries/Cabal/Cabal/Distribution/Simple/GHC.hs 2013-06-12 11:35:39.832840754 +0900 -@@ -837,6 +837,8 @@ - - dynamicOpts = vanillaOpts `mappend` mempty { - ghcOptDynamic = toFlag True, -+ ghcOptHiSuffix = toFlag "dyn_hi", -+ ghcOptObjSuffix = toFlag "dyn_o", - ghcOptExtra = ghcSharedOptions exeBi - } - -@@ -855,9 +857,9 @@ - -- with profiling. This is because the code that TH needs to - -- run at compile time needs to be the vanilla ABI so it can - -- be loaded up and run by the compiler. -- when (withProfExe lbi && -+ when ((withProfExe lbi || withDynExe lbi) && - EnableExtension TemplateHaskell `elem` allExtensions exeBi) $ -- runGhcProg exeProfOpts { ghcOptNoLink = toFlag True } -+ runGhcProg vanillaOpts { ghcOptNoLink = toFlag True } - - runGhcProg exeOpts { ghcOptOutputFile = toFlag (targetDir exeNameReal) } - diff --git a/ghc-cabal-unversion-docdir.patch b/ghc-cabal-unversion-docdir.patch deleted file mode 100644 index 9d0b026..0000000 --- a/ghc-cabal-unversion-docdir.patch +++ /dev/null @@ -1,13 +0,0 @@ ---- ghc-7.8/utils/ghc-cabal/Main.hs~ 2013-08-28 08:06:37.000000000 +0900 -+++ ghc-7.8/utils/ghc-cabal/Main.hs 2013-09-03 17:51:22.800653817 +0900 -@@ -251,8 +251,8 @@ - libsubdir = toPathTemplate "$pkgid", - docdir = toPathTemplate $ - if relocatableBuild -- then "$topdir/../doc/html/libraries/$pkgid" -- else (myDocdir "$pkgid"), -+ then "$topdir/../doc/html/libraries/$pkg" -+ else (myDocdir "$pkg"), - htmldir = toPathTemplate "$docdir" - } - diff --git a/ghc-use-system-libffi.patch b/ghc-use-system-libffi.patch deleted file mode 100644 index fb6d90a..0000000 --- a/ghc-use-system-libffi.patch +++ /dev/null @@ -1,73 +0,0 @@ -This patch could be replaced by a configure call if -http://hackage.haskell.org/trac/ghc/ticket/5743 were fixed. - -Index: ghc-7.6.1/rts/package.conf.in -=================================================================== ---- ghc-7.6.1.orig/rts/package.conf.in 2012-09-04 19:10:15.000000000 +0200 -+++ ghc-7.6.1/rts/package.conf.in 2012-10-08 13:06:55.167887121 +0200 -@@ -24,8 +24,9 @@ - hs-libraries: "HSrts" - - extra-libraries: -+ "ffi" - #ifdef HAVE_LIBM -- "m" /* for ldexp() */ -+ , "m" /* for ldexp() */ - #endif - #ifdef HAVE_LIBRT - , "rt" -Index: ghc-7.6.1/ghc.mk -=================================================================== ---- ghc-7.6.1.orig/ghc.mk 2012-09-04 19:10:15.000000000 +0200 -+++ ghc-7.6.1/ghc.mk 2012-10-08 13:06:55.171887120 +0200 -@@ -600,7 +600,6 @@ - $(MAYBE_GHCI) \ - driver/ghc \ - driver/haddock \ -- libffi \ - includes \ - rts - -Index: ghc-7.6.1/rts/ghc.mk -=================================================================== ---- ghc-7.6.1.orig/rts/ghc.mk 2012-09-04 19:10:15.000000000 +0200 -+++ ghc-7.6.1/rts/ghc.mk 2012-10-08 13:08:52.019882891 +0200 -@@ -177,12 +177,12 @@ - # Making a shared library for the RTS. - ifneq "$$(findstring dyn, $1)" "" - ifeq "$$(HostOS_CPP)" "mingw32" --$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend rts/dist/build/$$(LIBFFI_DLL) -+$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) rts/libs.depend - "$$(RM)" $$(RM_OPTS) $$@ - "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ - -no-auto-link-packages -Lrts/dist/build -l$(LIBFFI_WINDOWS_LIB) `cat rts/libs.depend` $$(rts_$1_OBJS) $$(ALL_RTS_DEF_LIBS) -o $$@ - else --$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend rts/dist/build/libffi$$(soext) -+$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) rts/libs.depend - "$$(RM)" $$(RM_OPTS) $$@ - "$$(rts_dist_HC)" -package-name rts -shared -dynamic -dynload deploy \ - -no-auto-link-packages -Lrts/dist/build -lffi `cat rts/libs.depend` $$(rts_$1_OBJS) \ -@@ -193,9 +193,9 @@ - endif - endif - else --$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) $$(rts_ffi_objs_stamp) -+$$(rts_$1_LIB) : $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) - "$$(RM)" $$(RM_OPTS) $$@ -- echo $$(rts_ffi_objs) $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ -+ echo $$(rts_$1_OBJS) $$(rts_$1_DTRACE_OBJS) | "$$(XARGS)" $$(XARGS_OPTS) "$$(AR_STAGE1)" \ - $$(AR_OPTS_STAGE1) $$(EXTRA_AR_ARGS_STAGE1) $$@ - endif - -@@ -509,10 +509,8 @@ - # installing - - INSTALL_LIBS += $(ALL_RTS_LIBS) --INSTALL_LIBS += $(wildcard rts/dist/build/libffi$(soext)*) --INSTALL_LIBS += $(wildcard rts/dist/build/$(LIBFFI_DLL)) - --install: install_libffi_headers -+install: - - .PHONY: install_libffi_headers - install_libffi_headers : diff --git a/ghc.spec b/ghc.spec index 51cf5f9..9307a0e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -43,8 +43,6 @@ Source4: ghc-doc-index Patch1: ghc-gen_contents_index-haddock-path.patch # add libffi include dir to ghc wrapper for archs using gcc/llc #Patch10: ghc-wrapper-libffi-include.patch -# unversion library html docdirs -Patch16: ghc-cabal-unversion-docdir.patch # warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch @@ -263,11 +261,6 @@ rm -r libffi-tarballs #%%patch10 -p1 -b .10-ffi %endif -# unversion pkgdoc htmldir -%if 0%{?fedora} >= 21 -%patch16 -p1 -b .orig -%endif - %patch20 -p1 -b .orig %ifarch aarch64 @@ -548,6 +541,7 @@ fi %changelog * Sun Jan 18 2015 Jens Petersen - 7.8.4-40 - production build +- version doc htmldirs again * Sat Jan 17 2015 Jens Petersen - 7.8.4-39 - update to 7.8.4 From c5e919bbca9a7773ec5ab74d535fb3d000745741 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 7 Feb 2015 16:55:30 +0100 Subject: [PATCH 389/530] bootstrap for secondary arches, with bindir/ghci --- ghc.spec | 24 +++++++++++------------- 1 file changed, 11 insertions(+), 13 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9307a0e..3fc18c3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,12 @@ # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 -#%%global without_testsuite 1 -#%%global without_prof 1 -#%%if 0%{?fedora} >= 22 -#%%{?ghc_bootstrap} -#%%else -#%%{?ghc_test} -#%%endif +%global ghc_bootstrapping 1 +%global without_testsuite 1 +%global without_prof 1 +%if 0%{?fedora} >= 22 +%{?ghc_bootstrap} +%else +%{?ghc_test} +%endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock @@ -28,7 +28,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 40%{?dist} +Release: 39.1%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -468,10 +468,8 @@ fi %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} -%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} -%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -539,9 +537,9 @@ fi %changelog -* Sun Jan 18 2015 Jens Petersen - 7.8.4-40 -- production build +* Sat Feb 7 2015 Jens Petersen - 7.8.4-39.1 - version doc htmldirs again +- all archs have bindir/ghci * Sat Jan 17 2015 Jens Petersen - 7.8.4-39 - update to 7.8.4 From 1857c31d258915b81945cb571db3e4208384a81c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 7 Feb 2015 18:25:23 +0100 Subject: [PATCH 390/530] update the arm64 patch for 7.8.4 --- ghc-arm64.patch | 10 +++++----- ghc.spec | 1 + 2 files changed, 6 insertions(+), 5 deletions(-) diff --git a/ghc-arm64.patch b/ghc-arm64.patch index 7652727..38ad80d 100644 --- a/ghc-arm64.patch +++ b/ghc-arm64.patch @@ -91,13 +91,13 @@ Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" ArchAlpha -> panic "maxSpillSlots ArchAlpha" ArchMipseb -> panic "maxSpillSlots ArchMipseb" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs +Index: ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs =================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/Main.hs 2014-07-10 10:16:42.529187516 +0200 +--- ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs.orig 2015-02-07 18:19:27.364827776 +0100 ++++ ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs 2015-02-07 18:20:46.813771354 +0100 @@ -207,6 +207,7 @@ - ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) first_id block_live sccs - ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) first_id block_live sccs + ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) entry_ids block_live sccs + ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) entry_ids block_live sccs ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" + ArchARM64 -> panic "linearRegAlloc ArchARM64" ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" diff --git a/ghc.spec b/ghc.spec index 3fc18c3..ba72ac6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -540,6 +540,7 @@ fi * Sat Feb 7 2015 Jens Petersen - 7.8.4-39.1 - version doc htmldirs again - all archs have bindir/ghci +- update the arm64 patch for 7.8.4 * Sat Jan 17 2015 Jens Petersen - 7.8.4-39 - update to 7.8.4 From 00c13d3cbc94be20008a844131c9f505348e64f2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 9 Feb 2015 17:05:08 +0100 Subject: [PATCH 391/530] production build; use %ghc_bootstrapping to control bootstrap setup --- ghc.spec | 18 ++++++++++++------ 1 file changed, 12 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index ba72ac6..087f64d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,7 @@ -# To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 +# To bootstrap build a new version of ghc: +#%%global ghc_bootstrapping 1 + +%if %{defined ghc_bootstrapping} %global without_testsuite 1 %global without_prof 1 %if 0%{?fedora} >= 22 @@ -9,6 +11,7 @@ %endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock +%endif # make sure to turn on shared libs for all arches # (for building on releases earlier than F22) @@ -28,7 +31,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 39.1%{?dist} +Release: 41%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -537,10 +540,13 @@ fi %changelog -* Sat Feb 7 2015 Jens Petersen - 7.8.4-39.1 -- version doc htmldirs again -- all archs have bindir/ghci +* Mon Feb 9 2015 Jens Petersen - 7.8.4-41 - update the arm64 patch for 7.8.4 +- all archs have bindir/ghci + +* Sun Jan 18 2015 Jens Petersen - 7.8.4-40 +- production build +- version doc htmldirs again * Sat Jan 17 2015 Jens Petersen - 7.8.4-39 - update to 7.8.4 From 14a6d06df66d3183d58babfd7b497d2811e5c3ca Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 15 Feb 2015 01:06:21 +0900 Subject: [PATCH 392/530] try "make -j16" on Intel arches to keep ABI hashes same as -40 --- ghc.spec | 9 ++++++++- 1 file changed, 8 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 087f64d..ac1fa22 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 41%{?dist} +Release: 42%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -343,6 +343,10 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" export LANG=en_US.utf8 +echo %{?_smp_mflags} +%ifarch %{ix86} x86_64 +%global _smp_mflags -j16 +%endif make %{?_smp_mflags} @@ -540,6 +544,9 @@ fi %changelog +* Sat Feb 14 2015 Jens Petersen - 7.8.4-42 +- try "make -j16" on Intel arches to keep ABI hashes same as -40 + * Mon Feb 9 2015 Jens Petersen - 7.8.4-41 - update the arm64 patch for 7.8.4 - all archs have bindir/ghci From 0d3cc88776637c378763f5d83031d6e3f4f1b906 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 15 Feb 2015 01:11:15 +0900 Subject: [PATCH 393/530] only echo _smp_mflags if it is defined --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index ac1fa22..dba5ee0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -343,7 +343,9 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" export LANG=en_US.utf8 +%if %{defined _smp_mflags} echo %{?_smp_mflags} +%endif %ifarch %{ix86} x86_64 %global _smp_mflags -j16 %endif From 5e438927a49a1a2f9e9e93010f780ff8afdeb283 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 15 Feb 2015 01:15:38 +0900 Subject: [PATCH 394/530] better _smp_mflags echo output --- ghc.spec | 4 +--- 1 file changed, 1 insertion(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index dba5ee0..2188814 100644 --- a/ghc.spec +++ b/ghc.spec @@ -343,9 +343,7 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" export LANG=en_US.utf8 -%if %{defined _smp_mflags} -echo %{?_smp_mflags} -%endif +echo _smp_mflags is '%{?_smp_mflags}' %ifarch %{ix86} x86_64 %global _smp_mflags -j16 %endif From e44e75832ee79ecd058a9fab24882a168c7db6bf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 15 Feb 2015 21:59:29 +0900 Subject: [PATCH 395/530] override "make %{?_smp_mflags}" in mock/koji if not -j16 - in koji HOSTNAME is "" - from testing in koji: -j8 was too small and -j12 seemed big enough --- ghc.spec | 15 ++++++++++++--- 1 file changed, 12 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2188814..c02f355 100644 --- a/ghc.spec +++ b/ghc.spec @@ -343,11 +343,20 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" export LANG=en_US.utf8 -echo _smp_mflags is '%{?_smp_mflags}' + +echo _smp_mflags is \'%{?_smp_mflags}\' +# NB for future ghc versions we should probably hardcode max -j4 instead for all builds to avoid this +MAKE_JOBS=%{?_smp_mflags} %ifarch %{ix86} x86_64 -%global _smp_mflags -j16 +# hack to perserve the high "make -j" ghc ABI hashes for 7.8.4 koji/mock builds +# (-j12 seems to be sufficient but not -j8) +if [ -z "$HOSTNAME" -a "%{?_smp_mflags}" != "-j16" ]; then + echo "Overriding for koji/mock Intel builds to preserve the ghc ABI hashes:" + MAKE_JOBS=-j16 +fi %endif -make %{?_smp_mflags} + +make $MAKE_JOBS %install From 0b41876861153c70abca3affd1a99ff9c18d2ee3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 1 Mar 2015 19:57:53 +0900 Subject: [PATCH 396/530] use llvm for aarch64 and fix build.mk BuildFlavour setup --- ghc.spec | 15 +++++++++++---- 1 file changed, 11 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index c02f355..9a2efd3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -123,6 +123,9 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm34 %endif +%ifarch aarch64 +BuildRequires: llvm +%endif %ifarch armv7hl aarch64 # patch22 and patch24 BuildRequires: autoconf, automake @@ -292,13 +295,13 @@ fi # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF %if %{undefined ghc_bootstrapping} -%ifnarch armv7hl armv5tel -BuildFlavour = perf -%else +%ifarch armv7hl armv5tel aarch64 BuildFlavour = perf-llvm +%else +BuildFlavour = perf %endif %else -%ifnarch armv7hl armv5tel +%ifarch armv7hl armv5tel aarch64 BuildFlavour = quick-llvm %else BuildFlavour = quick @@ -553,6 +556,10 @@ fi %changelog +* Sun Mar 1 2015 Jens Petersen +- use llvm for aarch64 +- fix build.mk BuildFlavour setup + * Sat Feb 14 2015 Jens Petersen - 7.8.4-42 - try "make -j16" on Intel arches to keep ABI hashes same as -40 From 8ae1316deb3e59a2f339f220a656ec27319f3ae5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 1 Mar 2015 20:04:16 +0900 Subject: [PATCH 397/530] setup make -j more carefully, add %build_minimum_smp minimum -j12 for intel, can be overriden with %build_minimum_smp --- ghc.spec | 29 ++++++++++++++++++++++------- 1 file changed, 22 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9a2efd3..74ced97 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,3 +1,8 @@ +# for F22 and F23 ghc-7.8.4, override to high "make -j" to preserve ABI hashes +# - set < 9 at our own risk +# (-j9 seems sufficent but to be safe use -j12) +%global build_minimum_smp 12 + # To bootstrap build a new version of ghc: #%%global ghc_bootstrapping 1 @@ -348,18 +353,27 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" export LANG=en_US.utf8 echo _smp_mflags is \'%{?_smp_mflags}\' -# NB for future ghc versions we should probably hardcode max -j4 instead for all builds to avoid this -MAKE_JOBS=%{?_smp_mflags} +# NB for future ghc versions maybe should hardcode max -j4 for all builds +# Though apparently this does not affect 7.10 +MAKE_JOBS=$(echo %{?_smp_mflags} | sed -e "s/^-j//") %ifarch %{ix86} x86_64 # hack to perserve the high "make -j" ghc ABI hashes for 7.8.4 koji/mock builds -# (-j12 seems to be sufficient but not -j8) -if [ -z "$HOSTNAME" -a "%{?_smp_mflags}" != "-j16" ]; then - echo "Overriding for koji/mock Intel builds to preserve the ghc ABI hashes:" - MAKE_JOBS=-j16 +# (-j9 seems to be sufficient but not -j8) +if [ "%{build_minimum_smp}" -le "8" ]; then + echo "** NB: ghc-7.8.4 needs to be built with 'make -j9' or higher to preserve the -j16 ABI hashes for F22/F23 i686 and x86_64 **" +fi +if [ -z "$MAKE_JOBS" -o "0$MAKE_JOBS" -le "%{build_minimum_smp}" ]; then + echo "Overriding 'make -j' SMP for Intel builds to preserve the ghc ABI hashes:" + MAKE_JOBS="%{build_minimum_smp}" +fi +%else +# keep < 9 for all other archs +if [ "0$MAKE_JOBS" -gt "8" ]; then + MAKE_JOBS=8 fi %endif -make $MAKE_JOBS +make ${MAKE_JOBS:+-j$MAKE_JOBS} %install @@ -559,6 +573,7 @@ fi * Sun Mar 1 2015 Jens Petersen - use llvm for aarch64 - fix build.mk BuildFlavour setup +- improve the smp make setup with build_minimum_smp * Sat Feb 14 2015 Jens Petersen - 7.8.4-42 - try "make -j16" on Intel arches to keep ABI hashes same as -40 From 7e41a8042a17d7df9d04880eb76d9f4337a2540d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 20 Mar 2015 09:12:59 +0900 Subject: [PATCH 398/530] aarch64 bootstrap without dyn ghc(i) and llvm, disable ld hardening on 64bit llvm needs 3.6 --- ghc.spec | 33 ++++++++++++++++++++++----------- 1 file changed, 22 insertions(+), 11 deletions(-) diff --git a/ghc.spec b/ghc.spec index 74ced97..6b7e93b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,10 +1,12 @@ -# for F22 and F23 ghc-7.8.4, override to high "make -j" to preserve ABI hashes +# for F22 and F23 intel ghc-7.8.4, override to high "make -j" to preserve ABI hashes # - set < 9 at our own risk # (-j9 seems sufficent but to be safe use -j12) %global build_minimum_smp 12 -# To bootstrap build a new version of ghc: -#%%global ghc_bootstrapping 1 +# To bootstrap build a new version of ghc, uncomment the following: +%ifarch aarch64 +%global ghc_bootstrapping 1 +%endif %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -36,7 +38,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 42%{?dist} +Release: 42.1%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -128,9 +130,6 @@ BuildRequires: python %ifarch armv7hl armv5tel BuildRequires: llvm34 %endif -%ifarch aarch64 -BuildRequires: llvm -%endif %ifarch armv7hl aarch64 # patch22 and patch24 BuildRequires: autoconf, automake @@ -300,13 +299,13 @@ fi # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF %if %{undefined ghc_bootstrapping} -%ifarch armv7hl armv5tel aarch64 +%ifarch armv7hl armv5tel BuildFlavour = perf-llvm %else BuildFlavour = perf %endif %else -%ifarch armv7hl armv5tel aarch64 +%ifarch armv7hl armv5tel BuildFlavour = quick-llvm %else BuildFlavour = quick @@ -319,6 +318,11 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif +%ifarch aarch64 +# aarch64 dynlinking causing runtime IO problems +# https://ghc.haskell.org/trac/ghc/ticket/9673 +DYNAMIC_GHC_PROGRAMS=NO +%endif ## for verbose build output #GhcStage1HcOpts=-v4 ## enable RTS debugging: @@ -334,6 +338,11 @@ done %ifarch aarch64 armv7hl autoreconf %endif +# x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC +# aarch64: /usr/bin/ld: /usr/lib64/ghc-7.6.3/libHSrts.a(RtsFlags.o)(.text+0x578): unresolvable R_AARCH64_ADR_PREL_PG_HI21 relocation against symbol `stdout@@GLIBC_2.17' +%ifarch x86_64 aarch64 +%global _hardened_ldflags %{nil} +%endif export CFLAGS="${CFLAGS:-%optflags}" export LDFLAGS="${LDFLAGS:-%__global_ldflags}" # * %%configure induces cross-build due to different target/host/build platform names @@ -501,8 +510,10 @@ fi %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} +%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} +%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs @@ -570,10 +581,10 @@ fi %changelog -* Sun Mar 1 2015 Jens Petersen -- use llvm for aarch64 +* Wed Mar 18 2015 Jens Petersen - 7.8.4-42.1 - fix build.mk BuildFlavour setup - improve the smp make setup with build_minimum_smp +- bootstrap for aarch64 without ghci (#1195231) * Sat Feb 14 2015 Jens Petersen - 7.8.4-42 - try "make -j16" on Intel arches to keep ABI hashes same as -40 From 31c538ec04adb718732c3cefce5550c9b028b17f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 20 Mar 2015 17:57:55 +0900 Subject: [PATCH 399/530] disable ld hardening also for armv7 and secondary 64bit archs --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 6b7e93b..fc5c839 100644 --- a/ghc.spec +++ b/ghc.spec @@ -340,7 +340,7 @@ autoreconf %endif # x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC # aarch64: /usr/bin/ld: /usr/lib64/ghc-7.6.3/libHSrts.a(RtsFlags.o)(.text+0x578): unresolvable R_AARCH64_ADR_PREL_PG_HI21 relocation against symbol `stdout@@GLIBC_2.17' -%ifarch x86_64 aarch64 +%ifarch x86_64 armv7hl aarch64 s390x ppc64 ppc64le %global _hardened_ldflags %{nil} %endif export CFLAGS="${CFLAGS:-%optflags}" @@ -585,6 +585,7 @@ fi - fix build.mk BuildFlavour setup - improve the smp make setup with build_minimum_smp - bootstrap for aarch64 without ghci (#1195231) +- disable ld hardening for F23 on 64bit and armv7hl * Sat Feb 14 2015 Jens Petersen - 7.8.4-42 - try "make -j16" on Intel arches to keep ABI hashes same as -40 From 4eb7d02023aae89e68fdd2350e3a15b6256d37ab Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Mar 2015 11:45:54 +0900 Subject: [PATCH 400/530] a primitive ABI checking script --- abi-check.sh | 14 ++++++++++++++ 1 file changed, 14 insertions(+) create mode 100644 abi-check.sh diff --git a/abi-check.sh b/abi-check.sh new file mode 100644 index 0000000..f2a47fd --- /dev/null +++ b/abi-check.sh @@ -0,0 +1,14 @@ +#!/bin/sh + +REL=$(rpm -q --qf "%{release}" ghc-compiler) +ARCH=$(arch) +PKGS=$(rpm -qa | grep -- -$REL | grep -v -- -devel | sort | sed -e "s/-[0-9.]\+-.*//") + +for i in $PKGS; do + LOCAL=$(rpm -q --provides $i | grep ^ghc\( | grep -v =) + REPO=$(dnf repoquery -q --provides $i | grep ^ghc\( | grep -v = | sort | uniq) + if [ "$LOCAL" != "$REPO" ]; then + echo $LOCAL + echo $REPO + fi +done From ad9efc0b8f40addc7d91fed9eec50b5622b3dfd5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Mar 2015 11:48:00 +0900 Subject: [PATCH 401/530] make abi-check.sh executable --- abi-check.sh | 0 1 file changed, 0 insertions(+), 0 deletions(-) mode change 100644 => 100755 abi-check.sh diff --git a/abi-check.sh b/abi-check.sh old mode 100644 new mode 100755 From 12566624b482d67e8bfc205cfe80b1f782fa7cb8 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Mar 2015 12:50:33 +0900 Subject: [PATCH 402/530] abi-check.sh now downloads builds from koji and compares their hashes --- abi-check.sh | 54 ++++++++++++++++++++++++++++++++++++++++++---------- 1 file changed, 44 insertions(+), 10 deletions(-) diff --git a/abi-check.sh b/abi-check.sh index f2a47fd..fc428f0 100755 --- a/abi-check.sh +++ b/abi-check.sh @@ -1,14 +1,48 @@ #!/bin/sh -REL=$(rpm -q --qf "%{release}" ghc-compiler) -ARCH=$(arch) -PKGS=$(rpm -qa | grep -- -$REL | grep -v -- -devel | sort | sed -e "s/-[0-9.]\+-.*//") - -for i in $PKGS; do - LOCAL=$(rpm -q --provides $i | grep ^ghc\( | grep -v =) - REPO=$(dnf repoquery -q --provides $i | grep ^ghc\( | grep -v = | sort | uniq) - if [ "$LOCAL" != "$REPO" ]; then - echo $LOCAL - echo $REPO +[ $# -ne 2 ] && echo "Usage: $(basename $0) ver-rel1 ver-rel2" && exit 1 + +if [ "$1" = "$2" ]; then + echo "ver-rel's must be different!" + exit 1 +fi + +#set -x + +mkdir -p koji +cd koji + +for i in $1 $2; do + if [ ! -d "$i" ]; then + mkdir -p $i/{x86_64,i686,armv7hl} + cd $i + for a in x86_64 i686 armv7hl; do + cd $a + koji download-build --arch=$a ghc-$i + cd .. + done + cd .. fi done + +for a in x86_64 i686 armv7hl; do + echo "= $a =" + for i in $1/$a/*; do + PKGVER=$(rpm -qp --qf "%{name}-%{version}" $i) + PKG2=$(ls $2/$a/$PKGVER*.$a.rpm) + PROV1=$(rpm -qp --provides $i | grep ^ghc\( | grep -v =) + PROV2=$(rpm -qp --provides $PKG2 | grep ^ghc\( | grep -v =) +# if [ -n "$PROV1" ]; then +# echo $PROV1 +# else +# echo "no provides for $i" +# fi + if [ -n "$PROV2" ]; then + if [ "$PROV1" != "$PROV2" ]; then + echo $PROV2 + fi +# else +# echo "no provides for $PKG2" + fi + done +done From 3f22c768eb298690fb6c85b67a27574223f5eed7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Mar 2015 12:52:09 +0900 Subject: [PATCH 403/530] aarch64 production build; use -j16 again on intel archs --- ghc.spec | 18 ++++++++++-------- 1 file changed, 10 insertions(+), 8 deletions(-) diff --git a/ghc.spec b/ghc.spec index fc5c839..46226b0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,12 +1,9 @@ -# for F22 and F23 intel ghc-7.8.4, override to high "make -j" to preserve ABI hashes -# - set < 9 at our own risk -# (-j9 seems sufficent but to be safe use -j12) -%global build_minimum_smp 12 +# for F22 and F23 intel ghc-7.8.4, force high "make -j" to preserve ABI hashes +# - set < 16 at your own risk +%global build_minimum_smp 16 # To bootstrap build a new version of ghc, uncomment the following: -%ifarch aarch64 -%global ghc_bootstrapping 1 -%endif +#%%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -38,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 42.1%{?dist} +Release: 43%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -581,6 +578,11 @@ fi %changelog +* Mon Mar 23 2015 Jens Petersen - 7.8.4-43 +- aarch64 production build +- must use "make -j16" for Intel arches to preserve ABI hashes + (-j12 changed array's hash on i686) + * Wed Mar 18 2015 Jens Petersen - 7.8.4-42.1 - fix build.mk BuildFlavour setup - improve the smp make setup with build_minimum_smp From bd9e01445e9c8715eb2f08738c2d2b6888cfead1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 23 Mar 2015 18:56:46 +0900 Subject: [PATCH 404/530] bootstrap aarch64 again for ghc-deps.sh fixes --- ghc.spec | 10 ++++++---- 1 file changed, 6 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 46226b0..a3ec693 100644 --- a/ghc.spec +++ b/ghc.spec @@ -3,7 +3,9 @@ %global build_minimum_smp 16 # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 +%ifarch aarch64 +%global ghc_bootstrapping 1 +%endif %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -35,7 +37,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 43%{?dist} +Release: 42.2%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -578,8 +580,8 @@ fi %changelog -* Mon Mar 23 2015 Jens Petersen - 7.8.4-43 -- aarch64 production build +* Mon Mar 23 2015 Jens Petersen - 7.8.4-42.2 +- aarch64 bootstrap build - must use "make -j16" for Intel arches to preserve ABI hashes (-j12 changed array's hash on i686) From 841d58b0284403df5b2ec6cdb22be638287d2330 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 30 Mar 2015 23:19:15 +0900 Subject: [PATCH 405/530] aarch64 production build --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index a3ec693..3e14576 100644 --- a/ghc.spec +++ b/ghc.spec @@ -3,9 +3,7 @@ %global build_minimum_smp 16 # To bootstrap build a new version of ghc, uncomment the following: -%ifarch aarch64 -%global ghc_bootstrapping 1 -%endif +#%%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -37,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 42.2%{?dist} +Release: 43%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -580,6 +578,9 @@ fi %changelog +* Mon Mar 30 2015 Jens Petersen - 7.8.4-43 +- aarch64 production build + * Mon Mar 23 2015 Jens Petersen - 7.8.4-42.2 - aarch64 bootstrap build - must use "make -j16" for Intel arches to preserve ABI hashes From c1e250e452cd1428bc886878aa62df665ee043df Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 10 Apr 2015 22:33:17 +0530 Subject: [PATCH 406/530] turn on SMP and ghci for aarch64 patch by Erik de Castro Lopo from https://ghc.haskell.org/trac/ghc/ticket/9673 --- ...ble-SMP-and-GHCi-support-for-Aarch64.patch | 34 +++++++++++++++++++ ghc.spec | 12 +++---- 2 files changed, 40 insertions(+), 6 deletions(-) create mode 100644 ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch diff --git a/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch b/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch new file mode 100644 index 0000000..0259f10 --- /dev/null +++ b/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch @@ -0,0 +1,34 @@ +From 44cee4852282f63393d532aad59c5cd865ff3ed6 Mon Sep 17 00:00:00 2001 +From: Erik de Castro Lopo +Date: Wed, 1 Apr 2015 04:46:01 +0000 +Subject: [PATCH] mk/config.mk.in : Enable SMP and GHCi support for Aarch64. + +--- + mk/config.mk.in | 4 ++-- + 1 file changed, 2 insertions(+), 2 deletions(-) + +diff --git a/mk/config.mk.in b/mk/config.mk.in +index f4cb52b..d6831c9 100644 +--- a/mk/config.mk.in ++++ b/mk/config.mk.in +@@ -172,7 +172,7 @@ HaveLibDL = @HaveLibDL@ + + # ArchSupportsSMP should be set iff there is support for that arch in + # includes/stg/SMP.h +-ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm))) ++ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm aarch64))) + + GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised)),YES,NO)) + +@@ -180,7 +180,7 @@ GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised + # has support for this OS/ARCH combination. + + OsSupportsGHCi=$(strip $(patsubst $(TargetOS_CPP), YES, $(findstring $(TargetOS_CPP), mingw32 cygwin32 linux solaris2 freebsd dragonfly netbsd openbsd darwin kfreebsdgnu))) +-ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm))) ++ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm aarch64))) + + ifeq "$(OsSupportsGHCi)$(ArchSupportsGHCi)" "YESYES" + GhcWithInterpreter=YES +-- +2.1.4 + diff --git a/ghc.spec b/ghc.spec index 3e14576..cca6a60 100644 --- a/ghc.spec +++ b/ghc.spec @@ -35,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 43%{?dist} +Release: 44%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -58,6 +58,7 @@ Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch Patch24: ghc-7.8-arm7-use-ld-gold-8976.patch Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch +Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch %global Cabal_ver 1.18.1.5 %global array_ver 0.5.0.0 @@ -272,6 +273,7 @@ rm -r libffi-tarballs %ifarch aarch64 %patch21 -p1 -b .orig +%patch26 -p1 -b .orig %endif %ifarch armv7hl @@ -315,11 +317,6 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif -%ifarch aarch64 -# aarch64 dynlinking causing runtime IO problems -# https://ghc.haskell.org/trac/ghc/ticket/9673 -DYNAMIC_GHC_PROGRAMS=NO -%endif ## for verbose build output #GhcStage1HcOpts=-v4 ## enable RTS debugging: @@ -578,6 +575,9 @@ fi %changelog +* Fri Apr 10 2015 Jens Petersen - 7.8.4-44 +- turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1210323) + * Mon Mar 30 2015 Jens Petersen - 7.8.4-43 - aarch64 production build From 2dec8072bded61c25644211253111d60fc054095 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 22 Apr 2015 19:04:55 +0900 Subject: [PATCH 407/530] use ld.gold for aarch64 and "make -j3" for s390 --- ghc-7.8-arm-use-ld-gold.patch | 42 +++++++++++++++++++++++++++++ ghc-7.8-arm7-use-ld-gold-8976.patch | 17 ------------ ghc.spec | 21 ++++++++++++--- 3 files changed, 59 insertions(+), 21 deletions(-) create mode 100644 ghc-7.8-arm-use-ld-gold.patch delete mode 100644 ghc-7.8-arm7-use-ld-gold-8976.patch diff --git a/ghc-7.8-arm-use-ld-gold.patch b/ghc-7.8-arm-use-ld-gold.patch new file mode 100644 index 0000000..46d572f --- /dev/null +++ b/ghc-7.8-arm-use-ld-gold.patch @@ -0,0 +1,42 @@ +armv7 by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 +arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd) + +--- ghc-7.8.4/aclocal.m4.24~ 2015-04-01 04:48:39.961193022 -0400 ++++ ghc-7.8.4/aclocal.m4 2015-04-01 04:50:19.708203082 -0400 +@@ -553,6 +553,14 @@ + $3="$$3 -D_HPUX_SOURCE" + $5="$$5 -D_HPUX_SOURCE" + ;; ++ arm*) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; ++ aarch64) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; + esac + + # If gcc knows about the stack protector, turn it off. +--- ghc-7.8.4/configure.ac~ 2014-12-22 14:08:24.000000000 -0500 ++++ ghc-7.8.4/configure.ac 2015-04-22 00:08:54.646110535 -0400 +@@ -587,7 +587,18 @@ + dnl ** Which ld to use? + dnl -------------------------------------------------------------- + FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) +-LdCmd="$LD" ++case $target in ++arm*linux* | aarch64*linux*) ++ # Arm requires use of the binutils ld.gold linker. ++ # This case should catch at least arm-unknown-linux-gnueabihf and ++ # arm-linux-androideabi. ++ FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) ++ LdCmd="$LD_GOLD" ++ ;; ++*) ++ LdCmd="$LD" ++ ;; ++esac + AC_SUBST([LdCmd]) + + dnl ** Which nm to use? diff --git a/ghc-7.8-arm7-use-ld-gold-8976.patch b/ghc-7.8-arm7-use-ld-gold-8976.patch deleted file mode 100644 index 6852db5..0000000 --- a/ghc-7.8-arm7-use-ld-gold-8976.patch +++ /dev/null @@ -1,17 +0,0 @@ -Patch by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 - -Index: ghc-7.8.3.20141119/aclocal.m4 -=================================================================== ---- ghc-7.8.3.20141119.orig/aclocal.m4 2014-12-08 18:49:28.207171714 +0100 -+++ ghc-7.8.3.20141119/aclocal.m4 2014-12-08 19:03:06.815522917 +0100 -@@ -553,6 +553,10 @@ - $3="$$3 -D_HPUX_SOURCE" - $5="$$5 -D_HPUX_SOURCE" - ;; -+ arm*) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; - esac - - # If gcc knows about the stack protector, turn it off. diff --git a/ghc.spec b/ghc.spec index cca6a60..705776a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -56,7 +56,7 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch Patch21: ghc-arm64.patch Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch -Patch24: ghc-7.8-arm7-use-ld-gold-8976.patch +Patch24: ghc-7.8-arm-use-ld-gold.patch Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch @@ -276,9 +276,12 @@ rm -r libffi-tarballs %patch26 -p1 -b .orig %endif +%ifarch armv7hl aarch64 +%patch24 -p1 -b .24~ +%endif + %ifarch armv7hl %patch22 -p1 -b .orig -%patch24 -p1 -b .24~ %patch25 -p1 -b .25~ %endif @@ -357,6 +360,7 @@ export LANG=en_US.utf8 echo _smp_mflags is \'%{?_smp_mflags}\' # NB for future ghc versions maybe should hardcode max -j4 for all builds +# (s390 seems ABI unstable under -j4) # Though apparently this does not affect 7.10 MAKE_JOBS=$(echo %{?_smp_mflags} | sed -e "s/^-j//") %ifarch %{ix86} x86_64 @@ -370,11 +374,18 @@ if [ -z "$MAKE_JOBS" -o "0$MAKE_JOBS" -le "%{build_minimum_smp}" ]; then MAKE_JOBS="%{build_minimum_smp}" fi %else +%ifarch s390 +# keep < 4 for s390 +if [ "0$MAKE_JOBS" -ge "4" ]; then + MAKE_JOBS=3 +fi +%else # keep < 9 for all other archs if [ "0$MAKE_JOBS" -gt "8" ]; then MAKE_JOBS=8 fi %endif +%endif make ${MAKE_JOBS:+-j$MAKE_JOBS} @@ -575,8 +586,10 @@ fi %changelog -* Fri Apr 10 2015 Jens Petersen - 7.8.4-44 -- turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1210323) +* Wed Apr 22 2015 Jens Petersen - 7.8.4-44 +- use ld.gold on aarch64 like for armv7 (Erik de Castro Lopo, #1195231) +- turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1195231) +- use "make -j3" for s390 (#1212374) * Mon Mar 30 2015 Jens Petersen - 7.8.4-43 - aarch64 production build From f65f1484ba69b6aef832ba72dae277cc222ac581 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 24 Apr 2015 14:11:15 +0900 Subject: [PATCH 408/530] use "make -j2" for s390 (#1212374) --- ghc.spec | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 705776a..74c9847 100644 --- a/ghc.spec +++ b/ghc.spec @@ -375,9 +375,9 @@ if [ -z "$MAKE_JOBS" -o "0$MAKE_JOBS" -le "%{build_minimum_smp}" ]; then fi %else %ifarch s390 -# keep < 4 for s390 -if [ "0$MAKE_JOBS" -ge "4" ]; then - MAKE_JOBS=3 +# use 2 for s390 +if [ "0$MAKE_JOBS" -ne "2" ]; then + MAKE_JOBS=2 fi %else # keep < 9 for all other archs @@ -589,7 +589,7 @@ fi * Wed Apr 22 2015 Jens Petersen - 7.8.4-44 - use ld.gold on aarch64 like for armv7 (Erik de Castro Lopo, #1195231) - turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1195231) -- use "make -j3" for s390 (#1212374) +- use "make -j2" for s390 (#1212374) * Mon Mar 30 2015 Jens Petersen - 7.8.4-43 - aarch64 production build From e8a98a8b8ae6bdd18db3dad73dff6693983c5cd9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 27 Apr 2015 15:49:42 +0900 Subject: [PATCH 409/530] revert ld.gold to armv7 only; static ghc progs for aarch64 - ld.gold patch didn't fix subprocess output problem aarch64 ghci crashes with both gold and bfd but TH seems to work --- ghc-7.8-arm-use-ld-gold.patch | 42 ----------------------------- ghc-7.8-arm7-use-ld-gold-8976.patch | 17 ++++++++++++ ghc.spec | 15 ++++++----- 3 files changed, 25 insertions(+), 49 deletions(-) delete mode 100644 ghc-7.8-arm-use-ld-gold.patch create mode 100644 ghc-7.8-arm7-use-ld-gold-8976.patch diff --git a/ghc-7.8-arm-use-ld-gold.patch b/ghc-7.8-arm-use-ld-gold.patch deleted file mode 100644 index 46d572f..0000000 --- a/ghc-7.8-arm-use-ld-gold.patch +++ /dev/null @@ -1,42 +0,0 @@ -armv7 by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 -arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd) - ---- ghc-7.8.4/aclocal.m4.24~ 2015-04-01 04:48:39.961193022 -0400 -+++ ghc-7.8.4/aclocal.m4 2015-04-01 04:50:19.708203082 -0400 -@@ -553,6 +553,14 @@ - $3="$$3 -D_HPUX_SOURCE" - $5="$$5 -D_HPUX_SOURCE" - ;; -+ arm*) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; -+ aarch64) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; - esac - - # If gcc knows about the stack protector, turn it off. ---- ghc-7.8.4/configure.ac~ 2014-12-22 14:08:24.000000000 -0500 -+++ ghc-7.8.4/configure.ac 2015-04-22 00:08:54.646110535 -0400 -@@ -587,7 +587,18 @@ - dnl ** Which ld to use? - dnl -------------------------------------------------------------- - FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) --LdCmd="$LD" -+case $target in -+arm*linux* | aarch64*linux*) -+ # Arm requires use of the binutils ld.gold linker. -+ # This case should catch at least arm-unknown-linux-gnueabihf and -+ # arm-linux-androideabi. -+ FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) -+ LdCmd="$LD_GOLD" -+ ;; -+*) -+ LdCmd="$LD" -+ ;; -+esac - AC_SUBST([LdCmd]) - - dnl ** Which nm to use? diff --git a/ghc-7.8-arm7-use-ld-gold-8976.patch b/ghc-7.8-arm7-use-ld-gold-8976.patch new file mode 100644 index 0000000..6852db5 --- /dev/null +++ b/ghc-7.8-arm7-use-ld-gold-8976.patch @@ -0,0 +1,17 @@ +Patch by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 + +Index: ghc-7.8.3.20141119/aclocal.m4 +=================================================================== +--- ghc-7.8.3.20141119.orig/aclocal.m4 2014-12-08 18:49:28.207171714 +0100 ++++ ghc-7.8.3.20141119/aclocal.m4 2014-12-08 19:03:06.815522917 +0100 +@@ -553,6 +553,10 @@ + $3="$$3 -D_HPUX_SOURCE" + $5="$$5 -D_HPUX_SOURCE" + ;; ++ arm*) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; + esac + + # If gcc knows about the stack protector, turn it off. diff --git a/ghc.spec b/ghc.spec index 74c9847..b52dfe0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -56,7 +56,7 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch Patch21: ghc-arm64.patch Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch -Patch24: ghc-7.8-arm-use-ld-gold.patch +Patch24: ghc-7.8-arm7-use-ld-gold-8976.patch Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch @@ -276,12 +276,9 @@ rm -r libffi-tarballs %patch26 -p1 -b .orig %endif -%ifarch armv7hl aarch64 -%patch24 -p1 -b .24~ -%endif - %ifarch armv7hl %patch22 -p1 -b .orig +%patch24 -p1 -b .24~ %patch25 -p1 -b .25~ %endif @@ -320,6 +317,11 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif +%ifarch aarch64 +# aarch64 dynlinking causing runtime IO problems +# https://ghc.haskell.org/trac/ghc/ticket/9673 +DYNAMIC_GHC_PROGRAMS=NO +%endif ## for verbose build output #GhcStage1HcOpts=-v4 ## enable RTS debugging: @@ -587,8 +589,7 @@ fi %changelog * Wed Apr 22 2015 Jens Petersen - 7.8.4-44 -- use ld.gold on aarch64 like for armv7 (Erik de Castro Lopo, #1195231) -- turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1195231) +- turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1203951) - use "make -j2" for s390 (#1212374) * Mon Mar 30 2015 Jens Petersen - 7.8.4-43 From 03c151c41aad847297f9e36379ae7ae632a20d51 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 11 Jun 2015 22:56:02 +0900 Subject: [PATCH 410/530] use ld.gold and re-enable dynamic linking of ghc programs Reverting "revert ld.gold to armv7 only; static ghc progs for aarch64" This reverts commit bc51500a32c12e58b0cdc8a50b0d551c8da177d8. --- ghc-7.8-arm-use-ld-gold.patch | 42 +++++++++++++++++++++++++++++ ghc-7.8-arm7-use-ld-gold-8976.patch | 17 ------------ ghc.spec | 17 ++++++------ 3 files changed, 51 insertions(+), 25 deletions(-) create mode 100644 ghc-7.8-arm-use-ld-gold.patch delete mode 100644 ghc-7.8-arm7-use-ld-gold-8976.patch diff --git a/ghc-7.8-arm-use-ld-gold.patch b/ghc-7.8-arm-use-ld-gold.patch new file mode 100644 index 0000000..46d572f --- /dev/null +++ b/ghc-7.8-arm-use-ld-gold.patch @@ -0,0 +1,42 @@ +armv7 by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 +arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd) + +--- ghc-7.8.4/aclocal.m4.24~ 2015-04-01 04:48:39.961193022 -0400 ++++ ghc-7.8.4/aclocal.m4 2015-04-01 04:50:19.708203082 -0400 +@@ -553,6 +553,14 @@ + $3="$$3 -D_HPUX_SOURCE" + $5="$$5 -D_HPUX_SOURCE" + ;; ++ arm*) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; ++ aarch64) ++ # On arm, link using gold ++ $3="$$3 -fuse-ld=gold" ++ ;; + esac + + # If gcc knows about the stack protector, turn it off. +--- ghc-7.8.4/configure.ac~ 2014-12-22 14:08:24.000000000 -0500 ++++ ghc-7.8.4/configure.ac 2015-04-22 00:08:54.646110535 -0400 +@@ -587,7 +587,18 @@ + dnl ** Which ld to use? + dnl -------------------------------------------------------------- + FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) +-LdCmd="$LD" ++case $target in ++arm*linux* | aarch64*linux*) ++ # Arm requires use of the binutils ld.gold linker. ++ # This case should catch at least arm-unknown-linux-gnueabihf and ++ # arm-linux-androideabi. ++ FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) ++ LdCmd="$LD_GOLD" ++ ;; ++*) ++ LdCmd="$LD" ++ ;; ++esac + AC_SUBST([LdCmd]) + + dnl ** Which nm to use? diff --git a/ghc-7.8-arm7-use-ld-gold-8976.patch b/ghc-7.8-arm7-use-ld-gold-8976.patch deleted file mode 100644 index 6852db5..0000000 --- a/ghc-7.8-arm7-use-ld-gold-8976.patch +++ /dev/null @@ -1,17 +0,0 @@ -Patch by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 - -Index: ghc-7.8.3.20141119/aclocal.m4 -=================================================================== ---- ghc-7.8.3.20141119.orig/aclocal.m4 2014-12-08 18:49:28.207171714 +0100 -+++ ghc-7.8.3.20141119/aclocal.m4 2014-12-08 19:03:06.815522917 +0100 -@@ -553,6 +553,10 @@ - $3="$$3 -D_HPUX_SOURCE" - $5="$$5 -D_HPUX_SOURCE" - ;; -+ arm*) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; - esac - - # If gcc knows about the stack protector, turn it off. diff --git a/ghc.spec b/ghc.spec index b52dfe0..a2ddbf1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -35,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 44%{?dist} +Release: 45%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -56,7 +56,7 @@ Patch20: ghc-glibc-2.20_BSD_SOURCE.patch Patch21: ghc-arm64.patch Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch -Patch24: ghc-7.8-arm7-use-ld-gold-8976.patch +Patch24: ghc-7.8-arm-use-ld-gold.patch Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch @@ -276,9 +276,12 @@ rm -r libffi-tarballs %patch26 -p1 -b .orig %endif +%ifarch armv7hl aarch64 +%patch24 -p1 -b .24~ +%endif + %ifarch armv7hl %patch22 -p1 -b .orig -%patch24 -p1 -b .24~ %patch25 -p1 -b .25~ %endif @@ -317,11 +320,6 @@ HADDOCK_DOCS = NO %if %{defined without_manual} BUILD_DOCBOOK_HTML = NO %endif -%ifarch aarch64 -# aarch64 dynlinking causing runtime IO problems -# https://ghc.haskell.org/trac/ghc/ticket/9673 -DYNAMIC_GHC_PROGRAMS=NO -%endif ## for verbose build output #GhcStage1HcOpts=-v4 ## enable RTS debugging: @@ -588,6 +586,9 @@ fi %changelog +* Thu Jun 11 2015 Jens Petersen - 7.8.4-45 +- use ld.gold on aarch64 like for armv7 (Erik de Castro Lopo, #1195231) + * Wed Apr 22 2015 Jens Petersen - 7.8.4-44 - turn on SMP and ghci for aarch64 (Erik de Castro Lopo, #1203951) - use "make -j2" for s390 (#1212374) From 449de140b6ef3762a703dfd98e4810bc63eb78f5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 15 Jun 2015 17:47:33 +0900 Subject: [PATCH 411/530] fix aarch64 case in aclocal.m4 --- ghc-7.8-arm-use-ld-gold.patch | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc-7.8-arm-use-ld-gold.patch b/ghc-7.8-arm-use-ld-gold.patch index 46d572f..8f29958 100644 --- a/ghc-7.8-arm-use-ld-gold.patch +++ b/ghc-7.8-arm-use-ld-gold.patch @@ -11,7 +11,7 @@ arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd + # On arm, link using gold + $3="$$3 -fuse-ld=gold" + ;; -+ aarch64) ++ aarch64*) + # On arm, link using gold + $3="$$3 -fuse-ld=gold" + ;; From 31adc233467e76abe07b1e48abae6cea751779f3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 16 Jun 2015 18:11:48 +0900 Subject: [PATCH 412/530] rebuild for unstable 64bit array ABI hash --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a2ddbf1..3825b8a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -35,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 45%{?dist} +Release: 46%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -586,6 +586,9 @@ fi %changelog +* Tue Jun 16 2015 Jens Petersen - 7.8.4-46 +- rebuild + * Thu Jun 11 2015 Jens Petersen - 7.8.4-45 - use ld.gold on aarch64 like for armv7 (Erik de Castro Lopo, #1195231) From a768c590d52f17c24a4ba7f6b2aed1a3d90d9d89 Mon Sep 17 00:00:00 2001 From: Dennis Gilmore Date: Wed, 3 Feb 2016 21:21:56 +0000 Subject: [PATCH 413/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_24_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 3825b8a..bd5d8aa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -35,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 46%{?dist} +Release: 47%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -586,6 +586,9 @@ fi %changelog +* Wed Feb 03 2016 Fedora Release Engineering - 7.8.4-47 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_24_Mass_Rebuild + * Tue Jun 16 2015 Jens Petersen - 7.8.4-46 - rebuild From 2664c8fb3e22571f62fbec2273fda01d80b2f4e6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 7 Mar 2016 22:38:31 +0900 Subject: [PATCH 414/530] drop the last use of %ghc_arches_with_ghci --- ghc.spec | 2 -- 1 file changed, 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index bd5d8aa..c8404c5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -515,10 +515,8 @@ fi %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg %{_bindir}/ghc-pkg-%{version} -%ifarch %ghc_arches_with_ghci %{_bindir}/ghci %{_bindir}/ghci-%{version} -%endif %{_bindir}/hp2ps %{_bindir}/hpc %ghost %{_bindir}/hsc2hs From 6dc67ae0f01ef074c7326afb62356091e01569a9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 8 Mar 2016 01:23:46 +0900 Subject: [PATCH 415/530] do not package ghc-split on MIPS (#1294873) --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index c8404c5..baeeb2f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -35,7 +35,7 @@ Version: 7.8.4 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml moved from haskell-platform to ghc-7.8.3 -Release: 47%{?dist} +Release: 48%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -531,7 +531,7 @@ fi %{ghclibdir}/bin/hsc2hs %{ghclibdir}/bin/runghc # unknown (unregisterized) archs -%ifnarch ppc64 s390 s390x ppc64le aarch64 +%ifnarch ppc64 s390 s390x ppc64le aarch64 %{mips} %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt @@ -584,6 +584,9 @@ fi %changelog +* Tue Mar 8 2016 Michal Toman - 7.8.4-48 +- do not package ghc-split on MIPS (#1294873) + * Wed Feb 03 2016 Fedora Release Engineering - 7.8.4-47 - Rebuilt for https://fedoraproject.org/wiki/Fedora_24_Mass_Rebuild From 84579a471be3063fab56092112f00b9f230a961a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 1 Jun 2016 15:08:06 +0900 Subject: [PATCH 416/530] update to 7.10.3 from petersen/ghc-7.10.3 copr - quick build - use 7.10.3b respin tarballs - no longer need: - ghc-glibc-2.20_BSD_SOURCE.patch - ghc-7.8-arm-use-ld-gold.patch - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch - ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch - build_minimum_smp - add Debian packages: - buildpath-abi-stability - no-missing-haddock-file-warning - reproducible-tmp-names - use llvm35 - add libraries-versions.sh script - all library versions updates except xhtml - BR ghc-rpm-macros-extra for all OS versions - support building on EL6 - deprecated libraries: haskell2010, haskell98, old-locale, old-time - symlink for integer-gmp2 - add llvm_major --- .gitignore | 4 + ghc-7.8-arm-use-ld-gold.patch | 42 --- ghc-Debian-buildpath-abi-stability.patch | 25 ++ ...bian-no-missing-haddock-file-warning.patch | 22 ++ ghc-Debian-reproducible-tmp-names.patch | 43 +++ ghc-arm64.patch | 322 ------------------ ...ble-SMP-and-GHCi-support-for-Aarch64.patch | 34 -- ghc-gen_contents_index-haddock-path.patch | 3 +- ghc-glibc-2.20_BSD_SOURCE.patch | 26 -- ghc-wrapper-libffi-include.patch | 6 - ghc.spec | 196 ++++------- libraries-versions.sh | 10 + sources | 4 +- 13 files changed, 179 insertions(+), 558 deletions(-) delete mode 100644 ghc-7.8-arm-use-ld-gold.patch create mode 100644 ghc-Debian-buildpath-abi-stability.patch create mode 100644 ghc-Debian-no-missing-haddock-file-warning.patch create mode 100644 ghc-Debian-reproducible-tmp-names.patch delete mode 100644 ghc-arm64.patch delete mode 100644 ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch delete mode 100644 ghc-glibc-2.20_BSD_SOURCE.patch delete mode 100644 ghc-wrapper-libffi-include.patch create mode 100755 libraries-versions.sh diff --git a/.gitignore b/.gitignore index ecf5cbb..4fa4000 100644 --- a/.gitignore +++ b/.gitignore @@ -16,3 +16,7 @@ testsuite-6.12.3.tar.bz2 /ghc-7.8.3-testsuite.tar.xz /ghc-7.8.4-src.tar.xz /ghc-7.8.4-testsuite.tar.xz +/ghc-7.8.4/ +/ghc-7.10.3/ +/ghc-7.10.3b-src.tar.xz +/ghc-7.10.3b-testsuite.tar.xz diff --git a/ghc-7.8-arm-use-ld-gold.patch b/ghc-7.8-arm-use-ld-gold.patch deleted file mode 100644 index 8f29958..0000000 --- a/ghc-7.8-arm-use-ld-gold.patch +++ /dev/null @@ -1,42 +0,0 @@ -armv7 by nomeata: https://ghc.haskell.org/trac/ghc/ticket/8976#comment:12 -arm64 backport of https://ghc.haskell.org/trac/ghc/ticket/9673#comment:28 (erikd) - ---- ghc-7.8.4/aclocal.m4.24~ 2015-04-01 04:48:39.961193022 -0400 -+++ ghc-7.8.4/aclocal.m4 2015-04-01 04:50:19.708203082 -0400 -@@ -553,6 +553,14 @@ - $3="$$3 -D_HPUX_SOURCE" - $5="$$5 -D_HPUX_SOURCE" - ;; -+ arm*) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; -+ aarch64*) -+ # On arm, link using gold -+ $3="$$3 -fuse-ld=gold" -+ ;; - esac - - # If gcc knows about the stack protector, turn it off. ---- ghc-7.8.4/configure.ac~ 2014-12-22 14:08:24.000000000 -0500 -+++ ghc-7.8.4/configure.ac 2015-04-22 00:08:54.646110535 -0400 -@@ -587,7 +587,18 @@ - dnl ** Which ld to use? - dnl -------------------------------------------------------------- - FP_ARG_WITH_PATH_GNU_PROG([LD], [ld], [ld]) --LdCmd="$LD" -+case $target in -+arm*linux* | aarch64*linux*) -+ # Arm requires use of the binutils ld.gold linker. -+ # This case should catch at least arm-unknown-linux-gnueabihf and -+ # arm-linux-androideabi. -+ FP_ARG_WITH_PATH_GNU_PROG([LD_GOLD], [ld.gold], [ld.gold]) -+ LdCmd="$LD_GOLD" -+ ;; -+*) -+ LdCmd="$LD" -+ ;; -+esac - AC_SUBST([LdCmd]) - - dnl ** Which nm to use? diff --git a/ghc-Debian-buildpath-abi-stability.patch b/ghc-Debian-buildpath-abi-stability.patch new file mode 100644 index 0000000..b6f46b6 --- /dev/null +++ b/ghc-Debian-buildpath-abi-stability.patch @@ -0,0 +1,25 @@ +Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 + +Index: ghc-7.10.1/compiler/iface/MkIface.hs +=================================================================== +--- ghc-7.10.1.orig/compiler/iface/MkIface.hs 2015-05-17 20:34:02.808643844 +0200 ++++ ghc-7.10.1/compiler/iface/MkIface.hs 2015-05-17 20:34:02.804643799 +0200 +@@ -611,7 +611,7 @@ + iface_hash <- computeFingerprint putNameLiterally + (mod_hash, + ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache +- mi_usages iface0, ++ usages, + sorted_deps, + mi_hpc iface0) + +@@ -644,6 +644,9 @@ + (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) + fix_fn = mi_fix_fn iface0 + ann_fn = mkIfaceAnnCache (mi_anns iface0) ++ -- Do not allow filenames to affect the interface ++ usages = [ case u of UsageFile _ fp -> UsageFile "" fp; _ -> u | u <- mi_usages iface0 ] ++ + + getOrphanHashes :: HscEnv -> [Module] -> IO [Fingerprint] + getOrphanHashes hsc_env mods = do diff --git a/ghc-Debian-no-missing-haddock-file-warning.patch b/ghc-Debian-no-missing-haddock-file-warning.patch new file mode 100644 index 0000000..b6ad6fa --- /dev/null +++ b/ghc-Debian-no-missing-haddock-file-warning.patch @@ -0,0 +1,22 @@ +Description: Do not emit a warning if the .haddock file is missing + As it is quite common on Debian installations to install the -dev package + without the -doc package. +Author: Joachim Breitner + +Index: ghc-7.10/utils/ghc-pkg/Main.hs +=================================================================== +--- ghc-7.10.orig/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200 ++++ ghc-7.10/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200 +@@ -1533,8 +1533,10 @@ + mapM_ (checkDir True "library-dirs") (libraryDirs pkg) + mapM_ (checkDir True "include-dirs") (includeDirs pkg) + mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg) +- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) +- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) ++ -- In Debian, it is quite normal that the package is installed without the ++ -- documentation. Do not print a warning there. ++ -- mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) ++ -- mapM_ (checkDirURL True "haddock-html") (haddockHTMLs pkg) + checkDuplicateModules pkg + checkExposedModules db_stack pkg + checkOtherModules pkg diff --git a/ghc-Debian-reproducible-tmp-names.patch b/ghc-Debian-reproducible-tmp-names.patch new file mode 100644 index 0000000..e1950ee --- /dev/null +++ b/ghc-Debian-reproducible-tmp-names.patch @@ -0,0 +1,43 @@ +This is an attempt to make GHC build reproducible. The name of .c files may end +up in the resulting binary (in the debug section), but not the directory. + +Instead of using the process id, create a hash from the command line arguments, +and assume that is going to be unique. + +Index: ghc/compiler/main/SysTools.hs +=================================================================== +--- ghc.orig/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100 ++++ ghc/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100 +@@ -66,6 +66,7 @@ + import Util + import DynFlags + import Exception ++import Fingerprint + + import Data.IORef + import Control.Monad +@@ -1152,8 +1153,8 @@ + mapping <- readIORef dir_ref + case Map.lookup tmp_dir mapping of + Nothing -> do +- pid <- getProcessID +- let prefix = tmp_dir "ghc" ++ show pid ++ "_" ++ pid <- getStableProcessID ++ let prefix = tmp_dir "ghc" ++ pid ++ "_" + mask_ $ mkTempDir prefix + Just dir -> return dir + where +@@ -1531,6 +1532,13 @@ + getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral + #endif + ++-- Debian-specific hack to get reproducible output, by not using the "random" ++-- pid, but rather something determinisic ++getStableProcessID :: IO String ++getStableProcessID = do ++ args <- getArgs ++ return $ take 4 $ show $ fingerprintString $ unwords args ++ + -- Divvy up text stream into lines, taking platform dependent + -- line termination into account. + linesPlatform :: String -> [String] diff --git a/ghc-arm64.patch b/ghc-arm64.patch deleted file mode 100644 index 38ad80d..0000000 --- a/ghc-arm64.patch +++ /dev/null @@ -1,322 +0,0 @@ -commit c29bf984dd20431cd4344e8a5c444d7a5be08389 -Author: Colin Watson -Date: Mon Apr 21 22:26:56 2014 -0500 -Bug: https://ghc.haskell.org/trac/ghc/ticket/7942 - - ghc: initial AArch64 patches - - Signed-off-by: Austin Seipp - -Index: ghc-7.8.3/aclocal.m4 -=================================================================== ---- ghc-7.8.3.orig/aclocal.m4 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/aclocal.m4 2014-07-10 10:16:42.529187516 +0200 -@@ -197,6 +197,9 @@ - GET_ARM_ISA() - test -z "[$]2" || eval "[$]2=\"ArchARM {armISA = \$ARM_ISA, armISAExt = \$ARM_ISA_EXT, armABI = \$ARM_ABI}\"" - ;; -+ aarch64) -+ test -z "[$]2" || eval "[$]2=ArchARM64" -+ ;; - alpha) - test -z "[$]2" || eval "[$]2=ArchAlpha" - ;; -@@ -1862,6 +1865,9 @@ - # converts cpu from gnu to ghc naming, and assigns the result to $target_var - AC_DEFUN([GHC_CONVERT_CPU],[ - case "$1" in -+ aarch64*) -+ $2="aarch64" -+ ;; - alpha*) - $2="alpha" - ;; -Index: ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/AsmCodeGen.lhs 2014-07-10 10:16:42.529187516 +0200 -@@ -166,6 +166,7 @@ - ArchPPC -> nCG' (ppcNcgImpl dflags) - ArchSPARC -> nCG' (sparcNcgImpl dflags) - ArchARM {} -> panic "nativeCodeGen: No NCG for ARM" -+ ArchARM64 -> panic "nativeCodeGen: No NCG for ARM64" - ArchPPC_64 -> panic "nativeCodeGen: No NCG for PPC 64" - ArchAlpha -> panic "nativeCodeGen: No NCG for Alpha" - ArchMipseb -> panic "nativeCodeGen: No NCG for mipseb" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Graph/TrivColorable.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -113,6 +113,7 @@ - ArchSPARC -> 14 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -137,6 +138,7 @@ - ArchSPARC -> 22 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -161,6 +163,7 @@ - ArchSPARC -> 11 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -@@ -185,6 +188,7 @@ - ArchSPARC -> 0 - ArchPPC_64 -> panic "trivColorable ArchPPC_64" - ArchARM _ _ _ -> panic "trivColorable ArchARM" -+ ArchARM64 -> panic "trivColorable ArchARM64" - ArchAlpha -> panic "trivColorable ArchAlpha" - ArchMipseb -> panic "trivColorable ArchMipseb" - ArchMipsel -> panic "trivColorable ArchMipsel" -Index: ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/RegAlloc/Linear/FreeRegs.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -74,6 +74,7 @@ - ArchPPC -> PPC.Instr.maxSpillSlots dflags - ArchSPARC -> SPARC.Instr.maxSpillSlots dflags - ArchARM _ _ _ -> panic "maxSpillSlots ArchARM" -+ ArchARM64 -> panic "maxSpillSlots ArchARM64" - ArchPPC_64 -> panic "maxSpillSlots ArchPPC_64" - ArchAlpha -> panic "maxSpillSlots ArchAlpha" - ArchMipseb -> panic "maxSpillSlots ArchMipseb" -Index: ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs -=================================================================== ---- ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs.orig 2015-02-07 18:19:27.364827776 +0100 -+++ ghc-7.8.4/compiler/nativeGen/RegAlloc/Linear/Main.hs 2015-02-07 18:20:46.813771354 +0100 -@@ -207,6 +207,7 @@ - ArchSPARC -> linearRegAlloc' dflags (frInitFreeRegs platform :: SPARC.FreeRegs) entry_ids block_live sccs - ArchPPC -> linearRegAlloc' dflags (frInitFreeRegs platform :: PPC.FreeRegs) entry_ids block_live sccs - ArchARM _ _ _ -> panic "linearRegAlloc ArchARM" -+ ArchARM64 -> panic "linearRegAlloc ArchARM64" - ArchPPC_64 -> panic "linearRegAlloc ArchPPC_64" - ArchAlpha -> panic "linearRegAlloc ArchAlpha" - ArchMipseb -> panic "linearRegAlloc ArchMipseb" -Index: ghc-7.8.3/compiler/nativeGen/TargetReg.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/nativeGen/TargetReg.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -54,6 +54,7 @@ - ArchSPARC -> SPARC.virtualRegSqueeze - ArchPPC_64 -> panic "targetVirtualRegSqueeze ArchPPC_64" - ArchARM _ _ _ -> panic "targetVirtualRegSqueeze ArchARM" -+ ArchARM64 -> panic "targetVirtualRegSqueeze ArchARM64" - ArchAlpha -> panic "targetVirtualRegSqueeze ArchAlpha" - ArchMipseb -> panic "targetVirtualRegSqueeze ArchMipseb" - ArchMipsel -> panic "targetVirtualRegSqueeze ArchMipsel" -@@ -70,6 +71,7 @@ - ArchSPARC -> SPARC.realRegSqueeze - ArchPPC_64 -> panic "targetRealRegSqueeze ArchPPC_64" - ArchARM _ _ _ -> panic "targetRealRegSqueeze ArchARM" -+ ArchARM64 -> panic "targetRealRegSqueeze ArchARM64" - ArchAlpha -> panic "targetRealRegSqueeze ArchAlpha" - ArchMipseb -> panic "targetRealRegSqueeze ArchMipseb" - ArchMipsel -> panic "targetRealRegSqueeze ArchMipsel" -@@ -85,6 +87,7 @@ - ArchSPARC -> SPARC.classOfRealReg - ArchPPC_64 -> panic "targetClassOfRealReg ArchPPC_64" - ArchARM _ _ _ -> panic "targetClassOfRealReg ArchARM" -+ ArchARM64 -> panic "targetClassOfRealReg ArchARM64" - ArchAlpha -> panic "targetClassOfRealReg ArchAlpha" - ArchMipseb -> panic "targetClassOfRealReg ArchMipseb" - ArchMipsel -> panic "targetClassOfRealReg ArchMipsel" -@@ -100,6 +103,7 @@ - ArchSPARC -> SPARC.mkVirtualReg - ArchPPC_64 -> panic "targetMkVirtualReg ArchPPC_64" - ArchARM _ _ _ -> panic "targetMkVirtualReg ArchARM" -+ ArchARM64 -> panic "targetMkVirtualReg ArchARM64" - ArchAlpha -> panic "targetMkVirtualReg ArchAlpha" - ArchMipseb -> panic "targetMkVirtualReg ArchMipseb" - ArchMipsel -> panic "targetMkVirtualReg ArchMipsel" -@@ -115,6 +119,7 @@ - ArchSPARC -> SPARC.regDotColor - ArchPPC_64 -> panic "targetRegDotColor ArchPPC_64" - ArchARM _ _ _ -> panic "targetRegDotColor ArchARM" -+ ArchARM64 -> panic "targetRegDotColor ArchARM64" - ArchAlpha -> panic "targetRegDotColor ArchAlpha" - ArchMipseb -> panic "targetRegDotColor ArchMipseb" - ArchMipsel -> panic "targetRegDotColor ArchMipsel" -Index: ghc-7.8.3/compiler/utils/Platform.hs -=================================================================== ---- ghc-7.8.3.orig/compiler/utils/Platform.hs 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/compiler/utils/Platform.hs 2014-07-10 10:16:42.529187516 +0200 -@@ -52,6 +52,7 @@ - , armISAExt :: [ArmISAExt] - , armABI :: ArmABI - } -+ | ArchARM64 - | ArchAlpha - | ArchMipseb - | ArchMipsel -Index: ghc-7.8.3/includes/stg/HaskellMachRegs.h -=================================================================== ---- ghc-7.8.3.orig/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/includes/stg/HaskellMachRegs.h 2014-07-10 10:16:42.533187516 +0200 -@@ -38,6 +38,7 @@ - #define MACHREGS_powerpc (powerpc_TARGET_ARCH || powerpc64_TARGET_ARCH || rs6000_TARGET_ARCH) - #define MACHREGS_sparc sparc_TARGET_ARCH - #define MACHREGS_arm arm_TARGET_ARCH -+#define MACHREGS_aarch64 aarch64_TARGET_ARCH - #define MACHREGS_darwin darwin_TARGET_OS - - #endif -Index: ghc-7.8.3/includes/stg/MachRegs.h -=================================================================== ---- ghc-7.8.3.orig/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/includes/stg/MachRegs.h 2014-07-10 10:16:42.533187516 +0200 -@@ -1,6 +1,6 @@ - /* ----------------------------------------------------------------------------- - * -- * (c) The GHC Team, 1998-2011 -+ * (c) The GHC Team, 1998-2014 - * - * Registers used in STG code. Might or might not correspond to - * actual machine registers. -@@ -531,6 +531,61 @@ - #define REG_D2 d11 - #endif - -+/* ----------------------------------------------------------------------------- -+ The ARMv8/AArch64 ABI register mapping -+ -+ The AArch64 provides 31 64-bit general purpose registers -+ and 32 128-bit SIMD/floating point registers. -+ -+ General purpose registers (see Chapter 5.1.1 in ARM IHI 0055B) -+ -+ Register | Special | Role in the procedure call standard -+ ---------+---------+------------------------------------ -+ SP | | The Stack Pointer -+ r30 | LR | The Link Register -+ r29 | FP | The Frame Pointer -+ r19-r28 | | Callee-saved registers -+ r18 | | The Platform Register, if needed; -+ | | or temporary register -+ r17 | IP1 | The second intra-procedure-call temporary register -+ r16 | IP0 | The first intra-procedure-call scratch register -+ r9-r15 | | Temporary registers -+ r8 | | Indirect result location register -+ r0-r7 | | Parameter/result registers -+ -+ -+ FPU/SIMD registers -+ -+ s/d/q/v0-v7 Argument / result/ scratch registers -+ s/d/q/v8-v15 callee-saved registers (must be preserved across subrutine calls, -+ but only bottom 64-bit value needs to be preserved) -+ s/d/q/v16-v31 temporary registers -+ -+ ----------------------------------------------------------------------------- */ -+ -+#elif MACHREGS_aarch64 -+ -+#define REG(x) __asm__(#x) -+ -+#define REG_Base r19 -+#define REG_Sp r20 -+#define REG_Hp r21 -+#define REG_R1 r22 -+#define REG_R2 r23 -+#define REG_R3 r24 -+#define REG_R4 r25 -+#define REG_R5 r26 -+#define REG_R6 r27 -+#define REG_SpLim r28 -+ -+#define REG_F1 s8 -+#define REG_F2 s9 -+#define REG_F3 s10 -+#define REG_F4 s11 -+ -+#define REG_D1 d12 -+#define REG_D2 d13 -+ - #else - - #error Cannot find platform to give register info for -Index: ghc-7.8.3/rts/StgCRun.c -=================================================================== ---- ghc-7.8.3.orig/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 -+++ ghc-7.8.3/rts/StgCRun.c 2014-07-10 10:16:42.533187516 +0200 -@@ -748,4 +748,70 @@ - } - #endif - -+#ifdef aarch64_HOST_ARCH -+ -+StgRegTable * -+StgRun(StgFunPtr f, StgRegTable *basereg) { -+ StgRegTable * r; -+ __asm__ volatile ( -+ /* -+ * save callee-saves registers on behalf of the STG code. -+ */ -+ "stp x19, x20, [sp, #-16]!\n\t" -+ "stp x21, x22, [sp, #-16]!\n\t" -+ "stp x23, x24, [sp, #-16]!\n\t" -+ "stp x25, x26, [sp, #-16]!\n\t" -+ "stp x27, x28, [sp, #-16]!\n\t" -+ "stp ip0, ip1, [sp, #-16]!\n\t" -+ "str lr, [sp, #-8]!\n\t" -+ -+ /* -+ * allocate some space for Stg machine's temporary storage. -+ * Note: RESERVER_C_STACK_BYTES has to be a round number here or -+ * the assembler can't assemble it. -+ */ -+ "str lr, [sp, %3]" -+ /* "sub sp, sp, %3\n\t" */ -+ /* -+ * Set BaseReg -+ */ -+ "mov x19, %2\n\t" -+ /* -+ * Jump to function argument. -+ */ -+ "bx %1\n\t" -+ -+ ".globl " STG_RETURN "\n\t" -+ ".type " STG_RETURN ", %%function\n" -+ STG_RETURN ":\n\t" -+ /* -+ * Free the space we allocated -+ */ -+ "ldr lr, [sp], %3\n\t" -+ /* "add sp, sp, %3\n\t" */ -+ /* -+ * Return the new register table, taking it from Stg's R1 (ARM64's R22). -+ */ -+ "mov %0, x22\n\t" -+ /* -+ * restore callee-saves registers. -+ */ -+ "ldr lr, [sp], #8\n\t" -+ "ldp ip0, ip1, [sp], #16\n\t" -+ "ldp x27, x28, [sp], #16\n\t" -+ "ldp x25, x26, [sp], #16\n\t" -+ "ldp x23, x24, [sp], #16\n\t" -+ "ldp x21, x22, [sp], #16\n\t" -+ "ldp x19, x20, [sp], #16\n\t" -+ -+ : "=r" (r) -+ : "r" (f), "r" (basereg), "i" (RESERVED_C_STACK_BYTES) -+ : "%x19", "%x20", "%x21", "%x22", "%x23", "%x24", "%x25", "%x26", "%x27", "%x28", -+ "%ip0", "%ip1", "%lr" -+ ); -+ return r; -+} -+ -+#endif -+ - #endif /* !USE_MINIINTERPRETER */ diff --git a/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch b/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch deleted file mode 100644 index 0259f10..0000000 --- a/ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch +++ /dev/null @@ -1,34 +0,0 @@ -From 44cee4852282f63393d532aad59c5cd865ff3ed6 Mon Sep 17 00:00:00 2001 -From: Erik de Castro Lopo -Date: Wed, 1 Apr 2015 04:46:01 +0000 -Subject: [PATCH] mk/config.mk.in : Enable SMP and GHCi support for Aarch64. - ---- - mk/config.mk.in | 4 ++-- - 1 file changed, 2 insertions(+), 2 deletions(-) - -diff --git a/mk/config.mk.in b/mk/config.mk.in -index f4cb52b..d6831c9 100644 ---- a/mk/config.mk.in -+++ b/mk/config.mk.in -@@ -172,7 +172,7 @@ HaveLibDL = @HaveLibDL@ - - # ArchSupportsSMP should be set iff there is support for that arch in - # includes/stg/SMP.h --ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm))) -+ArchSupportsSMP=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 sparc powerpc arm aarch64))) - - GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised)),YES,NO)) - -@@ -180,7 +180,7 @@ GhcWithSMP := $(strip $(if $(filter YESNO, $(ArchSupportsSMP)$(GhcUnregisterised - # has support for this OS/ARCH combination. - - OsSupportsGHCi=$(strip $(patsubst $(TargetOS_CPP), YES, $(findstring $(TargetOS_CPP), mingw32 cygwin32 linux solaris2 freebsd dragonfly netbsd openbsd darwin kfreebsdgnu))) --ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm))) -+ArchSupportsGHCi=$(strip $(patsubst $(TargetArch_CPP), YES, $(findstring $(TargetArch_CPP), i386 x86_64 powerpc sparc sparc64 arm aarch64))) - - ifeq "$(OsSupportsGHCi)$(ArchSupportsGHCi)" "YESYES" - GhcWithInterpreter=YES --- -2.1.4 - diff --git a/ghc-gen_contents_index-haddock-path.patch b/ghc-gen_contents_index-haddock-path.patch index 64ede18..e6819ee 100644 --- a/ghc-gen_contents_index-haddock-path.patch +++ b/ghc-gen_contents_index-haddock-path.patch @@ -1,7 +1,6 @@ --- ghc-7.6.3/libraries/gen_contents_index~ 2013-04-19 06:22:46.000000000 +0900 +++ ghc-7.6.3/libraries/gen_contents_index 2013-04-22 12:07:48.922152864 +0900 -@@ -60,7 +60,7 @@ - done +@@ -60,6 +60,6 @@ done else - HADDOCK=../../../../../bin/haddock diff --git a/ghc-glibc-2.20_BSD_SOURCE.patch b/ghc-glibc-2.20_BSD_SOURCE.patch deleted file mode 100644 index 0b9d94a..0000000 --- a/ghc-glibc-2.20_BSD_SOURCE.patch +++ /dev/null @@ -1,26 +0,0 @@ -From 7d738547049e686be4d90a19dcb9520418d5f72d Mon Sep 17 00:00:00 2001 -From: Jens Petersen -Date: Mon, 9 Jun 2014 15:48:41 +0900 -Subject: [PATCH] define _DEFAULT_SOURCE in Stg.h to avoid warnings from glibc - 2.20 (#9185) - ---- - includes/Stg.h | 2 ++ - 1 file changed, 2 insertions(+) - -diff --git a/includes/Stg.h b/includes/Stg.h -index 1707c9b..fbcf643 100644 ---- a/includes/Stg.h -+++ b/includes/Stg.h -@@ -47,6 +47,8 @@ - // We need _BSD_SOURCE so that math.h defines things like gamma - // on Linux - # define _BSD_SOURCE -+// glibc 2.20 deprecates _BSD_SOURCE in favour of _DEFAULT_SOURCE -+# define _DEFAULT_SOURCE - #endif - - #if IN_STG_CODE == 0 || defined(llvm_CC_FLAVOR) --- -1.9.3 - diff --git a/ghc-wrapper-libffi-include.patch b/ghc-wrapper-libffi-include.patch deleted file mode 100644 index 48870ec..0000000 --- a/ghc-wrapper-libffi-include.patch +++ /dev/null @@ -1,6 +0,0 @@ -diff -u ghc-7.4.1/ghc/ghc.wrapper\~ ghc-7.4.1/ghc/ghc.wrapper ---- ghc-7.4.1/ghc/ghc.wrapper~ 2012-02-02 03:10:32.000000000 +0900 -+++ ghc-7.4.1/ghc/ghc.wrapper 2012-05-02 19:39:05.503872527 +0900 -@@ -1 +1 @@ --exec "$executablename" -B"$topdir" ${1+"$@"} -+exec "$executablename" -B"$topdir" -optc-I$(pkg-config --variable=includedir libffi) ${1+"$@"} diff --git a/ghc.spec b/ghc.spec index baeeb2f..67a5a89 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,9 +1,5 @@ -# for F22 and F23 intel ghc-7.8.4, force high "make -j" to preserve ABI hashes -# - set < 16 at your own risk -%global build_minimum_smp 16 - # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 +%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -29,68 +25,63 @@ Name: ghc # part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.8.4 +Version: 7.10.3 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -# xhtml moved from haskell-platform to ghc-7.8.3 -Release: 48%{?dist} +# xhtml has not had a new release for some years +Release: 49%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport URL: http://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-src.tar.xz %if %{undefined without_testsuite} -Source2: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch -# add libffi include dir to ghc wrapper for archs using gcc/llc -#Patch10: ghc-wrapper-libffi-include.patch -# warning "_BSD_SOURCE and _SVID_SOURCE are deprecated, use _DEFAULT_SOURCE" -Patch20: ghc-glibc-2.20_BSD_SOURCE.patch # Debian patch -Patch21: ghc-arm64.patch Patch22: ghc-armv7-VFPv3D16--NEON.patch Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch -Patch24: ghc-7.8-arm-use-ld-gold.patch -Patch25: ghc-7.8-arm7_saner-linker-opt-handling-9873.patch -Patch26: ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch +Patch24: ghc-Debian-buildpath-abi-stability.patch +Patch26: ghc-Debian-no-missing-haddock-file-warning.patch +Patch27: ghc-Debian-reproducible-tmp-names.patch + +# 7.10.3 needs llvm-3.5 +%global llvm_major 3.5 -%global Cabal_ver 1.18.1.5 -%global array_ver 0.5.0.0 -%global base_ver 4.7.0.2 +# use "./libraries-versions.sh" to check versions +%global Cabal_ver 1.22.5.0 +%global array_ver 0.5.1.0 +%global base_ver 4.8.2.0 %global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.7.1.0 -%global bytestring_ver 0.10.4.0 -%global containers_ver 0.5.5.1 -%global deepseq_ver 1.3.0.2 -%global directory_ver 1.2.1.0 -%global filepath_ver 1.3.0.2 -%global ghc_prim_ver 0.3.1.0 -%global haskeline_ver 0.7.1.2 -%global haskell2010_ver 1.1.2.0 -%global haskell98_ver 2.0.0.3 -%global hoopl_ver 3.10.0.1 -%global hpc_ver 0.6.0.1 -%global integer_gmp_ver 0.5.1.0 -%global old_locale_ver 1.0.0.6 -%global old_time_ver 1.1.0.2 -%global pretty_ver 1.1.1.1 -%global process_ver 1.2.0.0 -%global template_haskell_ver 2.9.0.0 -%global terminfo_ver 0.4.0.0 -%global time_ver 1.4.2 -%global transformers_ver 0.3.0.0 -%global unix_ver 2.7.0.1 +%global binary_ver 0.7.5.0 +%global bytestring_ver 0.10.6.0 +%global containers_ver 0.5.6.2 +%global deepseq_ver 1.4.1.1 +%global directory_ver 1.2.2.0 +%global filepath_ver 1.4.0.0 +%global ghc_prim_ver 0.4.0.0 +%global haskeline_ver 0.7.2.1 +%global hoopl_ver 3.10.0.2 +%global hpc_ver 0.6.0.2 +%global integer_gmp_ver 1.0.0.0 +%global pretty_ver 1.1.2.0 +%global process_ver 1.2.3.0 +%global template_haskell_ver 2.10.0.0 +%global terminfo_ver 0.4.0.1 +%global time_ver 1.5.0.1 +%global transformers_ver 0.4.2.0 +%global unix_ver 2.7.1.0 %global xhtml_ver 3000.2.1 # fedora ghc has been bootstrapped on -# %{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 +# %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel # see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros ExcludeArch: sparc64 @@ -104,16 +95,11 @@ Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-f %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} %endif -%if 0%{?fedora} >= 20 || 0%{?rhel} >= 7 BuildRequires: ghc-rpm-macros-extra -%else -BuildRequires: ghc-rpm-macros -%endif BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel -BuildRequires: ghc-haskell98-devel BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel BuildRequires: gmp-devel @@ -126,10 +112,10 @@ BuildRequires: libxslt, docbook-style-xsl BuildRequires: python %endif %ifarch armv7hl armv5tel -BuildRequires: llvm34 +BuildRequires: llvm35 %endif -%ifarch armv7hl aarch64 -# patch22 and patch24 +%ifarch armv7hl +# patch22 BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} @@ -170,7 +156,7 @@ Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 %ifarch armv7hl armv5tel -Requires: llvm34 +Requires: llvm35 %endif %description compiler @@ -192,15 +178,15 @@ The package provides a cronjob for re-indexing installed library development documention. %endif -# ghclibdir also needs ghc_version_override for bootstrapping (ghc-deps.sh) +# ghclibdir also needs ghc_version_override for bootstrapping %global ghc_version_override %{version} -# currently only F21+ ghc-rpm-macros has ghc.attr -%if 0%{?fedora} < 21 +# EL7 rpm supports fileattrs ghc.attr +%if 0%{?rhel} && 0%{?rhel} < 7 # needs ghc_version_override for bootstrapping %global _use_internal_dependency_generator 0 -%global __find_provides %{_rpmconfigdir}/ghc-deps.sh --provides %{buildroot}%{ghclibdir} -%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} +%global __find_provides /usr/lib/rpm/rpmdeps --provides +%global __find_requires %{_rpmconfigdir}/ghc-deps.sh %{buildroot}%{ghclibdir} %endif %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} @@ -220,12 +206,8 @@ documention. %ghc_lib_subpackage -x ghc %{ghc_version_override} %undefine ghc_pkg_obsoletes %ghc_lib_subpackage haskeline %{haskeline_ver} -%ghc_lib_subpackage -l HaskellReport haskell2010 %{haskell2010_ver} -%ghc_lib_subpackage -l HaskellReport haskell98 %{haskell98_ver} %ghc_lib_subpackage hoopl %{hoopl_ver} %ghc_lib_subpackage hpc %{hpc_ver} -%ghc_lib_subpackage -l %BSDHaskellReport old-locale %{old_locale_ver} -%ghc_lib_subpackage -l %BSDHaskellReport old-time %{old_time_ver} %ghc_lib_subpackage pretty %{pretty_ver} %define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 %ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} @@ -235,8 +217,10 @@ documention. %ghc_lib_subpackage time %{time_ver} %ghc_lib_subpackage transformers %{transformers_ver} %ghc_lib_subpackage unix %{unix_ver} +%if %{undefined without_haddock} %ghc_lib_subpackage xhtml %{xhtml_ver} %endif +%endif %global version %{ghc_version_override} @@ -258,34 +242,22 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %prep -%setup -q -n %{name}-%{version} %{!?without_testsuite:-b2} +%setup -q -n %{name}-%{version} %{!?without_testsuite:-b1} # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig rm -r libffi-tarballs -%ifnarch %{ix86} x86_64 -#%%patch10 -p1 -b .10-ffi -%endif - -%patch20 -p1 -b .orig - -%ifarch aarch64 -%patch21 -p1 -b .orig -%patch26 -p1 -b .orig -%endif - -%ifarch armv7hl aarch64 -%patch24 -p1 -b .24~ -%endif - %ifarch armv7hl %patch22 -p1 -b .orig -%patch25 -p1 -b .25~ %endif %patch23 -p1 -b .orig +%patch24 -p1 -b .orig + +%patch26 -p1 -b .orig +%patch27 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -295,6 +267,9 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then fi %endif +mv libraries/integer-gmp{,.old} +ln -s integer-gmp2 libraries/integer-gmp + %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms @@ -327,12 +302,7 @@ BUILD_DOCBOOK_HTML = NO #EXTRA_HC_OPTS=-debug EOF -%ifarch aarch64 -for i in $(find . -name config.guess -o -name config.sub) ; do - [ -f /usr/lib/rpm/redhat/$(basename $i) ] && %{__rm} -f $i && %{__cp} -fv /usr/lib/rpm/redhat/$(basename $i) $i -done -%endif -%ifarch aarch64 armv7hl +%ifarch armv7hl autoreconf %endif # x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC @@ -341,7 +311,7 @@ autoreconf %global _hardened_ldflags %{nil} %endif export CFLAGS="${CFLAGS:-%optflags}" -export LDFLAGS="${LDFLAGS:-%__global_ldflags}" +export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" # * %%configure induces cross-build due to different target/host/build platform names # * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ @@ -349,45 +319,18 @@ export LDFLAGS="${LDFLAGS:-%__global_ldflags}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc --with-system-libffi \ + --with-gcc=%{_bindir}/gcc \ +%if 0%{?fedora} || 0%{?rhel} > 6 + --with-system-libffi \ +%endif %ifarch armv7hl armv5tel - --with-llc=%{_bindir}/llc-3.4 --with-opt=%{_bindir}/opt-3.4 \ + --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %endif %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" export LANG=en_US.utf8 - -echo _smp_mflags is \'%{?_smp_mflags}\' -# NB for future ghc versions maybe should hardcode max -j4 for all builds -# (s390 seems ABI unstable under -j4) -# Though apparently this does not affect 7.10 -MAKE_JOBS=$(echo %{?_smp_mflags} | sed -e "s/^-j//") -%ifarch %{ix86} x86_64 -# hack to perserve the high "make -j" ghc ABI hashes for 7.8.4 koji/mock builds -# (-j9 seems to be sufficient but not -j8) -if [ "%{build_minimum_smp}" -le "8" ]; then - echo "** NB: ghc-7.8.4 needs to be built with 'make -j9' or higher to preserve the -j16 ABI hashes for F22/F23 i686 and x86_64 **" -fi -if [ -z "$MAKE_JOBS" -o "0$MAKE_JOBS" -le "%{build_minimum_smp}" ]; then - echo "Overriding 'make -j' SMP for Intel builds to preserve the ghc ABI hashes:" - MAKE_JOBS="%{build_minimum_smp}" -fi -%else -%ifarch s390 -# use 2 for s390 -if [ "0$MAKE_JOBS" -ne "2" ]; then - MAKE_JOBS=2 -fi -%else -# keep < 9 for all other archs -if [ "0$MAKE_JOBS" -gt "8" ]; then - MAKE_JOBS=8 -fi -%endif -%endif - -make ${MAKE_JOBS:+-j$MAKE_JOBS} +make %{?_smp_mflags} %install @@ -419,12 +362,18 @@ echo "%doc libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist bin-package-db ghc # add rts libs -echo "%dir %{ghclibdir}/rts-1.0" >> ghc-base.files -ls %{buildroot}%{ghclibdir}/rts-1.0/libHS*.so >> ghc-base.files +echo "%dir %{ghclibdir}/rts" >> ghc-base.files +ls %{buildroot}%{ghclibdir}/rts/libHS*.so >> ghc-base.files +%if 0%{?rhel} && 0%{?rhel} < 7 +ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files +%endif sed -i -e "s|^%{buildroot}||g" ghc-base.files -ls -d %{buildroot}%{ghclibdir}/rts-1.0/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files +ls -d %{buildroot}%{ghclibdir}/rts/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files +%if 0%{?rhel} && 0%{?rhel} < 7 +ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files +%endif sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files @@ -536,7 +485,6 @@ fi %endif %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt -%{ghclibdir}/mkGmpDerivedConstants %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/platformConstants @@ -555,7 +503,7 @@ fi %{ghclibdir}/latex %if %{undefined without_manual} ## needs pandoc -#%{ghcdocbasedir}/Cabal +#%%{ghcdocbasedir}/Cabal %{ghcdocbasedir}/haddock %{ghcdocbasedir}/users_guide %endif diff --git a/libraries-versions.sh b/libraries-versions.sh new file mode 100755 index 0000000..4b51e27 --- /dev/null +++ b/libraries-versions.sh @@ -0,0 +1,10 @@ +#!/bin/sh + +if [ ! -d libraries ]; then + echo Is CWD a ghc source tree? + exit 1 +fi + +cd libraries + +grep -i ^version: Cabal/Cabal/Cabal.cabal */*.cabal | grep -v -e "\(Win32\|gmp.old\|gmp2\|integer-simple\|ghc-boot\)" | sed -e "s!/.*: \+!_ver !" diff --git a/sources b/sources index dff0a54..bf52373 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -91f74cf9d813603cc3145528db4bbead ghc-7.8.4-src.tar.xz -3cc3353d99518be7e7b2d78ebd5460b5 ghc-7.8.4-testsuite.tar.xz +d614735d9dac67432f8c6df7e45c76f7 ghc-7.10.3b-src.tar.xz +a2df2aaf3424127f0811c42d386c079b ghc-7.10.3b-testsuite.tar.xz From e5796cf8e5389585fc2f7cf5df8152c22d69520f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 3 Jun 2016 16:09:01 +0900 Subject: [PATCH 417/530] add missing changelog for 7.10.3-49! --- ghc.spec | 22 ++++++++++++++++++++++ 1 file changed, 22 insertions(+) diff --git a/ghc.spec b/ghc.spec index 67a5a89..c01c766 100644 --- a/ghc.spec +++ b/ghc.spec @@ -532,6 +532,28 @@ fi %changelog +* Wed Jun 1 2016 Jens Petersen - 7.10.3-49 +- quick build +- use 7.10.3b respin tarballs +- no longer need: + - ghc-glibc-2.20_BSD_SOURCE.patch + - ghc-7.8-arm-use-ld-gold.patch + - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch + - ghc-config.mk.in-Enable-SMP-and-GHCi-support-for-Aarch64.patch + - build_minimum_smp +- add Debian packages: + - buildpath-abi-stability + - no-missing-haddock-file-warning + - reproducible-tmp-names +- use llvm35 +- add libraries-versions.sh script +- all library versions updates except xhtml +- BR ghc-rpm-macros-extra for all OS versions +- support building on EL6 +- deprecated libraries: haskell2010, haskell98, old-locale, old-time +- symlink for integer-gmp2 +- add llvm_major + * Tue Mar 8 2016 Michal Toman - 7.8.4-48 - do not package ghc-split on MIPS (#1294873) From e285b9dffeb68ad61cdf5f2fdd63ae52463038d6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 3 Jun 2016 16:09:48 +0900 Subject: [PATCH 418/530] perf build --- ghc.spec | 10 ++++++++-- 1 file changed, 8 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index c01c766..593d3ab 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 +#%%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -31,7 +31,7 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 49%{?dist} +Release: 50%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -532,6 +532,12 @@ fi %changelog +* Fri Jun 3 2016 Jens Petersen - 7.10.3-50 +- perf build +- http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-1.html +- http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-2.html +- http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-3.html + * Wed Jun 1 2016 Jens Petersen - 7.10.3-49 - quick build - use 7.10.3b respin tarballs From aa524cd42636fc70cd5648d96a73acda03e1e063 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 12 Jul 2016 14:45:27 +0900 Subject: [PATCH 419/530] obsolete haskell98 and haskell2010 --- ghc.spec | 7 ++++++- 1 file changed, 6 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 593d3ab..e03aef0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -31,7 +31,7 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 50%{?dist} +Release: 51%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -194,7 +194,9 @@ documention. %if %{defined ghclibdir} %ghc_lib_subpackage Cabal %{Cabal_ver} %ghc_lib_subpackage -l %BSDHaskellReport array %{array_ver} +%define ghc_pkg_obsoletes ghc-haskell98-devel <= 2.0.0.3, ghc-haskell2010-devel <= 1.1.2.0 %ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base %{base_ver} +%undefine ghc_pkg_obsoletes %ghc_lib_subpackage binary %{binary_ver} %ghc_lib_subpackage bytestring %{bytestring_ver} %ghc_lib_subpackage -l %BSDHaskellReport containers %{containers_ver} @@ -532,6 +534,9 @@ fi %changelog +* Tue Jul 12 2016 Jens Petersen - 7.10.3-51 +- obsolete haskell98 and haskell2010 + * Fri Jun 3 2016 Jens Petersen - 7.10.3-50 - perf build - http://downloads.haskell.org/~ghc/7.10.3/docs/html/users_guide/release-7-10-1.html From 5fe7eac5b58789dfcf885898e484a8e97b745232 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 13 Jul 2016 17:17:40 +0900 Subject: [PATCH 420/530] add an ABI change check to prevent unexpected hash changes --- ghc.spec | 13 +++++++++++++ 1 file changed, 13 insertions(+) diff --git a/ghc.spec b/ghc.spec index e03aef0..25140e3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -432,6 +432,18 @@ rm testghc/* make test %endif +# check the ABI hashes +%if %{undefined ghc_bootstrapping} +for i in %{ghc_packages_list}; do +old=$(ghc-pkg field $i id --simple-output) +new=$(/usr/libexec/ghc-pkg/wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) +if [ "$old" != "$new" ]; then + echo "ABI hash for $i changed!:" + echo "$old -> $new" + exit 1 +done +%endif + %post compiler # Alas, GHC, Hugs, and nhc all come with different set of tools in @@ -536,6 +548,7 @@ fi %changelog * Tue Jul 12 2016 Jens Petersen - 7.10.3-51 - obsolete haskell98 and haskell2010 +- add an ABI change check to prevent unexpected ghc package hash changes * Fri Jun 3 2016 Jens Petersen - 7.10.3-50 - perf build From fe10edb8a2593db3a2255b16c16f6d59d49318b4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 13 Jul 2016 18:58:26 +0900 Subject: [PATCH 421/530] ABI check tweaks and fix --- ghc.spec | 17 +++++++++++------ 1 file changed, 11 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index 25140e3..ab99d0f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -434,14 +434,19 @@ make test # check the ABI hashes %if %{undefined ghc_bootstrapping} +echo "Checking package ABI hashes..." for i in %{ghc_packages_list}; do -old=$(ghc-pkg field $i id --simple-output) -new=$(/usr/libexec/ghc-pkg/wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) -if [ "$old" != "$new" ]; then - echo "ABI hash for $i changed!:" - echo "$old -> $new" - exit 1 + old=$(ghc-pkg field $i id --simple-output) + new=$(/usr/libexec/ghc-pkg/wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) + if [ "$old" != "$new" ]; then + echo "ABI hash for $i changed!:" >&2 + echo " $old -> $new" >&2 + exit 1 + else + echo "($old unchanged)" + fi done +echo "done." %endif From 4fd9c1754c991df561a04e03097f1f54bbc0584d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 14 Jul 2016 14:55:11 +0900 Subject: [PATCH 422/530] more ABI hash fix/improvements --- ghc.spec | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index ab99d0f..6d0ec91 100644 --- a/ghc.spec +++ b/ghc.spec @@ -434,19 +434,22 @@ make test # check the ABI hashes %if %{undefined ghc_bootstrapping} -echo "Checking package ABI hashes..." +echo "Checking package ABI hashes:" for i in %{ghc_packages_list}; do old=$(ghc-pkg field $i id --simple-output) - new=$(/usr/libexec/ghc-pkg/wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) + new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) if [ "$old" != "$new" ]; then echo "ABI hash for $i changed!:" >&2 echo " $old -> $new" >&2 - exit 1 + ghc_abi_hash_change=yes else echo "($old unchanged)" fi done -echo "done." +if [ "$ghc_abi_hash_change" = "yes" ]; then + echo "ghc ABI hash change: aborting build!" >&2 + exit 1 +fi %endif From 1516cd3aea7ef14e3ed8eb2fae0bad79788e7686 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 14 Jul 2016 16:35:20 +0900 Subject: [PATCH 423/530] the ABI hash checking requires all of ghc to be installed --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index 6d0ec91..289c84b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -94,6 +94,8 @@ Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} +# for ABI hash checking +BuildRequires: ghc = %{version} %endif BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-binary-devel From 9c3dd64d1f6d059ce625214811c06be4efaa1849 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 5 Sep 2016 17:37:07 +0900 Subject: [PATCH 424/530] update subpackaging for latest ghc-rpm-macros --- ghc.spec | 42 +++++++++++++++++++++--------------------- 1 file changed, 21 insertions(+), 21 deletions(-) diff --git a/ghc.spec b/ghc.spec index 289c84b..d0d41d1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -194,35 +194,35 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_lib_subpackage Cabal %{Cabal_ver} -%ghc_lib_subpackage -l %BSDHaskellReport array %{array_ver} +%ghc_lib_subpackage Cabal-%{Cabal_ver} +%ghc_lib_subpackage -l %BSDHaskellReport array-%{array_ver} %define ghc_pkg_obsoletes ghc-haskell98-devel <= 2.0.0.3, ghc-haskell2010-devel <= 1.1.2.0 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base %{base_ver} +%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage binary %{binary_ver} -%ghc_lib_subpackage bytestring %{bytestring_ver} -%ghc_lib_subpackage -l %BSDHaskellReport containers %{containers_ver} -%ghc_lib_subpackage -l %BSDHaskellReport deepseq %{deepseq_ver} -%ghc_lib_subpackage -l %BSDHaskellReport directory %{directory_ver} -%ghc_lib_subpackage filepath %{filepath_ver} +%ghc_lib_subpackage binary-%{binary_ver} +%ghc_lib_subpackage bytestring-%{bytestring_ver} +%ghc_lib_subpackage -l %BSDHaskellReport containers-%{containers_ver} +%ghc_lib_subpackage -l %BSDHaskellReport deepseq-%{deepseq_ver} +%ghc_lib_subpackage -l %BSDHaskellReport directory-%{directory_ver} +%ghc_lib_subpackage filepath-%{filepath_ver} %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: -%ghc_lib_subpackage -x ghc %{ghc_version_override} +%ghc_lib_subpackage -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage haskeline %{haskeline_ver} -%ghc_lib_subpackage hoopl %{hoopl_ver} -%ghc_lib_subpackage hpc %{hpc_ver} -%ghc_lib_subpackage pretty %{pretty_ver} +%ghc_lib_subpackage haskeline-%{haskeline_ver} +%ghc_lib_subpackage hoopl-%{hoopl_ver} +%ghc_lib_subpackage hpc-%{hpc_ver} +%ghc_lib_subpackage pretty-%{pretty_ver} %define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 -%ghc_lib_subpackage -l %BSDHaskellReport process %{process_ver} +%ghc_lib_subpackage -l %BSDHaskellReport process-%{process_ver} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage template-haskell %{template_haskell_ver} -%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo %{terminfo_ver} -%ghc_lib_subpackage time %{time_ver} -%ghc_lib_subpackage transformers %{transformers_ver} -%ghc_lib_subpackage unix %{unix_ver} +%ghc_lib_subpackage template-haskell-%{template_haskell_ver} +%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo-%{terminfo_ver} +%ghc_lib_subpackage time-%{time_ver} +%ghc_lib_subpackage transformers-%{transformers_ver} +%ghc_lib_subpackage unix-%{unix_ver} %if %{undefined without_haddock} -%ghc_lib_subpackage xhtml %{xhtml_ver} +%ghc_lib_subpackage xhtml-%{xhtml_ver} %endif %endif From 2ba2ba11a5b4a41cc6227c118c26d83028d5bfb1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 28 Sep 2016 18:17:28 +0900 Subject: [PATCH 425/530] use %license --- ghc.spec | 7 ++++--- 1 file changed, 4 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index d0d41d1..9a7a104 100644 --- a/ghc.spec +++ b/ghc.spec @@ -344,7 +344,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%doc libraries/$name/LICENSE" >> ghc-$name.files +echo "%license libraries/$name/LICENSE" >> ghc-$name.files done # ghc-base should own ghclibdir @@ -359,7 +359,7 @@ echo "%dir %{ghclibdir}" >> ghc-base.files cat ghc-%1.files >> ghc-%2.files\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ -echo "%doc libraries/LICENSE.%1" >> ghc-%2.files +echo "%license libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base @@ -483,7 +483,8 @@ fi %files %files compiler -%doc ANNOUNCE LICENSE +%license LICENSE +%doc ANNOUNCE %{_bindir}/ghc %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg From d486e5db122f52fe12b3fe47cf263422b02e8b71 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 7 Oct 2016 18:25:20 +0900 Subject: [PATCH 426/530] backport some trivial changes from github fedora-haskell/ghc ghclibdocdir -> ghc_html_libraries_dir ghcdocbasedir -> ghc_html_dir --- ghc.spec | 42 +++++++++++++++++++----------------------- 1 file changed, 19 insertions(+), 23 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9a7a104..75a7687 100644 --- a/ghc.spec +++ b/ghc.spec @@ -4,11 +4,7 @@ %if %{defined ghc_bootstrapping} %global without_testsuite 1 %global without_prof 1 -%if 0%{?fedora} >= 22 %{?ghc_bootstrap} -%else -%{?ghc_test} -%endif ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock %endif @@ -406,7 +402,7 @@ cd .. %endif # we package the library license files separately -find %{buildroot}%ghclibdocdir -name LICENSE -exec rm '{}' ';' +find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';' %check @@ -505,7 +501,7 @@ fi %{ghclibdir}/bin/hsc2hs %{ghclibdir}/bin/runghc # unknown (unregisterized) archs -%ifnarch ppc64 s390 s390x ppc64le aarch64 %{mips} +%ifnarch ppc64 s390 s390x ppc64le %{mips} aarch64 %{ghclibdir}/ghc-split %endif %{ghclibdir}/ghc-usage.txt @@ -518,7 +514,7 @@ fi %{ghclibdir}/unlit %{_mandir}/man1/ghc.* %dir %{_docdir}/ghc -%dir %{ghcdocbasedir} +%dir %{ghc_html_dir} %if %{undefined without_haddock} %{_bindir}/ghc-doc-index %{_bindir}/haddock @@ -528,23 +524,23 @@ fi %{ghclibdir}/latex %if %{undefined without_manual} ## needs pandoc -#%%{ghcdocbasedir}/Cabal -%{ghcdocbasedir}/haddock -%{ghcdocbasedir}/users_guide +#%%{ghc_html_dir}/Cabal +%{ghc_html_dir}/haddock +%{ghc_html_dir}/users_guide %endif -%dir %{ghcdocbasedir}/libraries -%{ghcdocbasedir}/libraries/frames.html -%{ghcdocbasedir}/libraries/gen_contents_index -%{ghcdocbasedir}/libraries/hslogo-16.png -%{ghcdocbasedir}/libraries/ocean.css -%{ghcdocbasedir}/libraries/prologue.txt -%{ghcdocbasedir}/libraries/synopsis.png -%{ghcdocbasedir}/index.html -%ghost %{ghcdocbasedir}/libraries/doc-index*.html -%ghost %{ghcdocbasedir}/libraries/haddock-util.js -%ghost %{ghcdocbasedir}/libraries/index*.html -%ghost %{ghcdocbasedir}/libraries/minus.gif -%ghost %{ghcdocbasedir}/libraries/plus.gif +%dir %{ghc_html_dir}/libraries +%{ghc_html_dir}/libraries/frames.html +%{ghc_html_dir}/libraries/gen_contents_index +%{ghc_html_dir}/libraries/hslogo-16.png +%{ghc_html_dir}/libraries/ocean.css +%{ghc_html_dir}/libraries/prologue.txt +%{ghc_html_dir}/libraries/synopsis.png +%{ghc_html_dir}/index.html +%ghost %{ghc_html_dir}/libraries/doc-index*.html +%ghost %{ghc_html_dir}/libraries/haddock-util.js +%ghost %{ghc_html_dir}/libraries/index*.html +%ghost %{ghc_html_dir}/libraries/minus.gif +%ghost %{ghc_html_dir}/libraries/plus.gif %{_localstatedir}/lib/ghc %endif From b4b15942b13c2bb004671efc4e6e1f9eaf01f699 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 26 Oct 2016 11:43:58 +0900 Subject: [PATCH 427/530] some lesser spec file cleanups - drop ghc_without_shared comment block - drop mention of haskell-platform - update url to https - drop dph and feldspar obsoletes - minor refresh and reformat of description - obsolete ghc-doc-index when building without_haddock --- ghc.spec | 52 ++++++++++++++++++++++++++-------------------------- 1 file changed, 26 insertions(+), 26 deletions(-) diff --git a/ghc.spec b/ghc.spec index 75a7687..7536e5f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,17 +9,10 @@ #%%undefine without_haddock %endif -# make sure to turn on shared libs for all arches -# (for building on releases earlier than F22) -%if %{defined ghc_without_shared} -%undefine ghc_without_shared -%endif - %global space %(echo -n ' ') %global BSDHaskellReport BSD%{space}and%{space}HaskellReport Name: ghc -# part of haskell-platform # ghc must be rebuilt after a version bump to avoid ABI change problems Version: 7.10.3 # Since library subpackages are versioned: @@ -27,11 +20,11 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 51%{?dist} +Release: 52%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport -URL: http://haskell.org/ghc/ +URL: https://haskell.org/ghc/ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-src.tar.xz %if %{undefined without_testsuite} Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-testsuite.tar.xz @@ -75,19 +68,11 @@ Patch27: ghc-Debian-reproducible-tmp-names.patch %global unix_ver 2.7.1.0 %global xhtml_ver 3000.2.1 - # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel -# see ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -ExcludeArch: sparc64 -Obsoletes: ghc-dph-base < 0.5, ghc-dph-base-devel < 0.5, ghc-dph-base-prof < 0.5 -Obsoletes: ghc-dph-par < 0.5, ghc-dph-par-devel < 0.5, ghc-dph-par-prof < 0.5 -Obsoletes: ghc-dph-prim-interface < 0.5, ghc-dph-prim-interface-devel < 0.5, ghc-dph-interface-prim-prof < 0.5 -Obsoletes: ghc-dph-prim-par < 0.5, ghc-dph-prim-par-devel < 0.5, ghc-dph-prim-par-prof < 0.5 -Obsoletes: ghc-dph-prim-seq < 0.5, ghc-dph-prim-seq-devel < 0.5, ghc-dph-prim-seq-prof < 0.5 -Obsoletes: ghc-dph-seq < 0.5, ghc-dph-seq-devel < 0.5, ghc-dph-seq-prof < 0.5 -Obsoletes: ghc-feldspar-language < 0.4, ghc-feldspar-language-devel < 0.4, ghc-feldspar-language-prof < 0.4 +# see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros + %if %{undefined ghc_bootstrapping} BuildRequires: ghc-compiler = %{version} # for ABI hash checking @@ -127,21 +112,24 @@ Requires: ghc-ghc-devel = %{version}-%{release} GHC is a state-of-the-art, open source, compiler and interactive environment for the functional language Haskell. Highlights: -- GHC supports the entire Haskell 2010 language plus various extensions. +- GHC supports the entire Haskell 2010 language plus a wide variety of + extensions. - GHC has particularly good support for concurrency and parallelism, including support for Software Transactional Memory (STM). -- GHC generates fast code, particularly for concurrent programs - (check the results on the "Computer Language Benchmarks Game"). +- GHC generates fast code, particularly for concurrent programs. + Take a look at GHC's performance on The Computer Language Benchmarks Game. - GHC works on several platforms including Windows, Mac, Linux, most varieties of Unix, and several different processor architectures. -- GHC has extensive optimisation capabilities, - including inter-module optimisation. +- GHC has extensive optimisation capabilities, including inter-module + optimisation. - GHC compiles Haskell code either directly to native code or using LLVM as a back-end. GHC can also generate C code as an intermediate target for porting to new platforms. The interactive environment compiles Haskell to bytecode, and supports execution of mixed bytecode/compiled programs. -- Profiling is supported, both by time/allocation and heap profiling. -- GHC comes with core libraries, and thousands more are available on Hackage. +- Profiling is supported, both by time/allocation and various kinds of heap + profiling. +- GHC comes with several libraries, and thousands more are available on Hackage. + %package compiler Summary: GHC compiler and utilities @@ -153,6 +141,9 @@ Requires(post): chkconfig Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 +%if %{defined without_haddock} +Obsoletes: ghc-doc-index < %{version}-%{release} +%endif %ifarch armv7hl armv5tel Requires: llvm35 %endif @@ -164,6 +155,7 @@ The ghc libraries are provided by ghc-libraries. To install all of ghc (including the ghc library), install the main ghc package. + %if %{undefined without_haddock} %package doc-index Summary: GHC library development documentation indexing @@ -176,6 +168,7 @@ The package provides a cronjob for re-indexing installed library development documention. %endif + # ghclibdir also needs ghc_version_override for bootstrapping %global ghc_version_override %{version} @@ -553,6 +546,13 @@ fi %changelog +* Wed Oct 26 2016 Jens Petersen - 7.10.3-52 +- use license macro +- update subpackaging for latest ghc-rpm-macros +- minor spec file cleanups +- drop old dph and feldspar obsoletes +- obsoletes ghc-doc-index when without_haddock + * Tue Jul 12 2016 Jens Petersen - 7.10.3-51 - obsolete haskell98 and haskell2010 - add an ABI change check to prevent unexpected ghc package hash changes From a373e18cef87867b2929f871dbd9b8dbdbf67e33 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 26 Oct 2016 12:46:05 +0900 Subject: [PATCH 428/530] BR perl --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index 7536e5f..716ad61 100644 --- a/ghc.spec +++ b/ghc.spec @@ -90,6 +90,7 @@ BuildRequires: libffi-devel # for terminfo BuildRequires: ncurses-devel # for man and docs +BuildRequires: perl BuildRequires: libxslt, docbook-style-xsl %if %{undefined without_testsuite} BuildRequires: python @@ -552,6 +553,7 @@ fi - minor spec file cleanups - drop old dph and feldspar obsoletes - obsoletes ghc-doc-index when without_haddock +- BR perl * Tue Jul 12 2016 Jens Petersen - 7.10.3-51 - obsolete haskell98 and haskell2010 From b47ee8e0c92190881d4fdad63abdff1cacd2b562 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 26 Oct 2016 15:26:19 +0900 Subject: [PATCH 429/530] condition removal of libffi-tarballs for rhel7/fedora --- ghc.spec | 2 ++ 1 file changed, 2 insertions(+) diff --git a/ghc.spec b/ghc.spec index 716ad61..83183a1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -241,7 +241,9 @@ except the ghc library, which is installed by the toplevel ghc metapackage. # gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig +%if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs +%endif %ifarch armv7hl %patch22 -p1 -b .orig From a638574b93317a62f7557ee66d3d6a42c0ba7944 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 26 Oct 2016 15:27:24 +0900 Subject: [PATCH 430/530] quote echo'd %license and %dir macros --- ghc.spec | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 83183a1..27810b6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -336,11 +336,11 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -echo "%license libraries/$name/LICENSE" >> ghc-$name.files +echo "%%license libraries/$name/LICENSE" >> ghc-$name.files done # ghc-base should own ghclibdir -echo "%dir %{ghclibdir}" >> ghc-base.files +echo "%%dir %{ghclibdir}" >> ghc-base.files %ghc_gen_filelists bin-package-db %{bin_package_db_ver} %ghc_gen_filelists ghc %{ghc_version_override} @@ -351,14 +351,14 @@ echo "%dir %{ghclibdir}" >> ghc-base.files cat ghc-%1.files >> ghc-%2.files\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ -echo "%license libraries/LICENSE.%1" >> ghc-%2.files +echo "%%license libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base %merge_filelist bin-package-db ghc # add rts libs -echo "%dir %{ghclibdir}/rts" >> ghc-base.files +echo "%%dir %{ghclibdir}/rts" >> ghc-base.files ls %{buildroot}%{ghclibdir}/rts/libHS*.so >> ghc-base.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files From 2f90b421e68eab3a5ae1d442eca968329c3396d3 Mon Sep 17 00:00:00 2001 From: Igor Gnatenko Date: Thu, 12 Jan 2017 17:30:28 +0100 Subject: [PATCH 431/530] Rebuild for readline 7.x Signed-off-by: Igor Gnatenko --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 27810b6..26d17ae 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,7 +20,7 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 52%{?dist} +Release: 53%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -549,6 +549,9 @@ fi %changelog +* Thu Jan 12 2017 Igor Gnatenko - 7.10.3-53 +- Rebuild for readline 7.x + * Wed Oct 26 2016 Jens Petersen - 7.10.3-52 - use license macro - update subpackaging for latest ghc-rpm-macros From cbdfd212995bea2baa5b33d4d4a8c8529afa3447 Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Fri, 10 Feb 2017 10:30:21 +0000 Subject: [PATCH 432/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_26_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 26d17ae..e742076 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,7 +20,7 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 53%{?dist} +Release: 54%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -549,6 +549,9 @@ fi %changelog +* Fri Feb 10 2017 Fedora Release Engineering - 7.10.3-54 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_26_Mass_Rebuild + * Thu Jan 12 2017 Igor Gnatenko - 7.10.3-53 - Rebuild for readline 7.x From 6db3dc36a5f04b1cb31c868499b0b9e4454070aa Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 13 Feb 2017 19:29:47 +0900 Subject: [PATCH 433/530] fix rebuild with latest ghc-rpm-macros; config llc and optc --- ghc.spec | 54 ++++++++++++++++++++++++++++-------------------------- 1 file changed, 28 insertions(+), 26 deletions(-) diff --git a/ghc.spec b/ghc.spec index e742076..a19fdbd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,7 +20,7 @@ Version: 7.10.3 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 54%{?dist} +Release: 55%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -78,7 +78,7 @@ BuildRequires: ghc-compiler = %{version} # for ABI hash checking BuildRequires: ghc = %{version} %endif -BuildRequires: ghc-rpm-macros-extra +BuildRequires: ghc-rpm-macros-extra >= 1.6.15 BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel @@ -184,35 +184,35 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} %if %{defined ghclibdir} -%ghc_lib_subpackage Cabal-%{Cabal_ver} -%ghc_lib_subpackage -l %BSDHaskellReport array-%{array_ver} +%ghc_lib_subpackage -d Cabal-%{Cabal_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport array-%{array_ver} %define ghc_pkg_obsoletes ghc-haskell98-devel <= 2.0.0.3, ghc-haskell2010-devel <= 1.1.2.0 -%ghc_lib_subpackage -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage binary-%{binary_ver} -%ghc_lib_subpackage bytestring-%{bytestring_ver} -%ghc_lib_subpackage -l %BSDHaskellReport containers-%{containers_ver} -%ghc_lib_subpackage -l %BSDHaskellReport deepseq-%{deepseq_ver} -%ghc_lib_subpackage -l %BSDHaskellReport directory-%{directory_ver} -%ghc_lib_subpackage filepath-%{filepath_ver} +%ghc_lib_subpackage -d binary-%{binary_ver} +%ghc_lib_subpackage -d bytestring-%{bytestring_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-%{containers_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-%{deepseq_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-%{directory_ver} +%ghc_lib_subpackage -d filepath-%{filepath_ver} %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: -%ghc_lib_subpackage -x ghc-%{ghc_version_override} +%ghc_lib_subpackage -d -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage haskeline-%{haskeline_ver} -%ghc_lib_subpackage hoopl-%{hoopl_ver} -%ghc_lib_subpackage hpc-%{hpc_ver} -%ghc_lib_subpackage pretty-%{pretty_ver} +%ghc_lib_subpackage -d haskeline-%{haskeline_ver} +%ghc_lib_subpackage -d hoopl-%{hoopl_ver} +%ghc_lib_subpackage -d hpc-%{hpc_ver} +%ghc_lib_subpackage -d pretty-%{pretty_ver} %define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 -%ghc_lib_subpackage -l %BSDHaskellReport process-%{process_ver} +%ghc_lib_subpackage -d -l %BSDHaskellReport process-%{process_ver} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage template-haskell-%{template_haskell_ver} -%ghc_lib_subpackage -c ncurses-devel%{?_isa} terminfo-%{terminfo_ver} -%ghc_lib_subpackage time-%{time_ver} -%ghc_lib_subpackage transformers-%{transformers_ver} -%ghc_lib_subpackage unix-%{unix_ver} +%ghc_lib_subpackage -d template-haskell-%{template_haskell_ver} +%ghc_lib_subpackage -d -c ncurses-devel%{?_isa} terminfo-%{terminfo_ver} +%ghc_lib_subpackage -d time-%{time_ver} +%ghc_lib_subpackage -d transformers-%{transformers_ver} +%ghc_lib_subpackage -d unix-%{unix_ver} %if %{undefined without_haddock} -%ghc_lib_subpackage xhtml-%{xhtml_ver} +%ghc_lib_subpackage -d xhtml-%{xhtml_ver} %endif %endif @@ -316,12 +316,10 @@ export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --with-gcc=%{_bindir}/gcc \ + --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %if 0%{?fedora} || 0%{?rhel} > 6 --with-system-libffi \ %endif -%ifarch armv7hl armv5tel - --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ -%endif %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" @@ -549,6 +547,10 @@ fi %changelog +* Mon Feb 13 2017 Jens Petersen - 7.10.3-55 +- use new ghc_lib_subpackage -d option to fix handling of .files +- configure llc-3.5 and opt-3.5 explicitly for all arch's + * Fri Feb 10 2017 Fedora Release Engineering - 7.10.3-54 - Rebuilt for https://fedoraproject.org/wiki/Fedora_26_Mass_Rebuild From b7696275b3bba1eb3b9732ab54dbec06d14c9362 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Feb 2017 13:54:58 +0900 Subject: [PATCH 434/530] update to ghc-8.0.2 --- .gitignore | 2 + ghc-8.0.2-Cabal-dynlibdir.patch | 11 ++ ...bian-no-missing-haddock-file-warning.patch | 10 +- ghc-Debian-osdecommitmemory-compat.patch | 39 ++++ ghc-Debian-reproducible-tmp-names.patch | 16 +- ghc-Debian-x32-use-native-x86_64-insn.patch | 27 +++ ghc.spec | 186 +++++++++--------- sources | 4 +- 8 files changed, 189 insertions(+), 106 deletions(-) create mode 100644 ghc-8.0.2-Cabal-dynlibdir.patch create mode 100644 ghc-Debian-osdecommitmemory-compat.patch create mode 100644 ghc-Debian-x32-use-native-x86_64-insn.patch diff --git a/.gitignore b/.gitignore index 4fa4000..bf56600 100644 --- a/.gitignore +++ b/.gitignore @@ -20,3 +20,5 @@ testsuite-6.12.3.tar.bz2 /ghc-7.10.3/ /ghc-7.10.3b-src.tar.xz /ghc-7.10.3b-testsuite.tar.xz +/ghc-8.0.2-testsuite.tar.xz +/ghc-8.0.2-src.tar.xz diff --git a/ghc-8.0.2-Cabal-dynlibdir.patch b/ghc-8.0.2-Cabal-dynlibdir.patch new file mode 100644 index 0000000..3f55fa3 --- /dev/null +++ b/ghc-8.0.2-Cabal-dynlibdir.patch @@ -0,0 +1,11 @@ +--- ghc-8.0.1.20161117/libraries/Cabal/Cabal/Distribution/Simple/InstallDirs.hs~ 2016-11-18 07:08:46.000000000 +0900 ++++ ghc-8.0.1.20161117/libraries/Cabal/Cabal/Distribution/Simple/InstallDirs.hs 2016-12-07 18:19:02.670468156 +0900 +@@ -186,7 +186,7 @@ + JHC -> "$compiler" + LHC -> "$compiler" + UHC -> "$pkgid" +- _other -> "$abi", ++ _other -> "$compiler/$pkgkey", + libexecdir = case buildOS of + Windows -> "$prefix" "$libname" + _other -> "$prefix" "libexec", diff --git a/ghc-Debian-no-missing-haddock-file-warning.patch b/ghc-Debian-no-missing-haddock-file-warning.patch index b6ad6fa..eac921e 100644 --- a/ghc-Debian-no-missing-haddock-file-warning.patch +++ b/ghc-Debian-no-missing-haddock-file-warning.patch @@ -3,12 +3,12 @@ Description: Do not emit a warning if the .haddock file is missing without the -doc package. Author: Joachim Breitner -Index: ghc-7.10/utils/ghc-pkg/Main.hs +Index: ghc-8.0.2/utils/ghc-pkg/Main.hs =================================================================== ---- ghc-7.10.orig/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200 -+++ ghc-7.10/utils/ghc-pkg/Main.hs 2015-07-22 11:17:04.787751658 +0200 -@@ -1533,8 +1533,10 @@ - mapM_ (checkDir True "library-dirs") (libraryDirs pkg) +--- ghc-8.0.2.orig/utils/ghc-pkg/Main.hs ++++ ghc-8.0.2/utils/ghc-pkg/Main.hs +@@ -1588,8 +1588,10 @@ + mapM_ (checkDir True "dynamic-library-dirs") (libraryDynDirs pkg) mapM_ (checkDir True "include-dirs") (includeDirs pkg) mapM_ (checkDir True "framework-dirs") (frameworkDirs pkg) - mapM_ (checkFile True "haddock-interfaces") (haddockInterfaces pkg) diff --git a/ghc-Debian-osdecommitmemory-compat.patch b/ghc-Debian-osdecommitmemory-compat.patch new file mode 100644 index 0000000..2c84d94 --- /dev/null +++ b/ghc-Debian-osdecommitmemory-compat.patch @@ -0,0 +1,39 @@ +Description: rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory +Author: Ben Gamari +Origin: upstream, https://phabricator.haskell.org/D2780 +Bug: https://ghc.haskell.org/trac/ghc/ticket/12865 +Bug-Debian: https://bugs.debian.org/847677 +--- +This patch header follows DEP-3: http://dep.debian.net/deps/dep3/ +Index: ghc-8.0.2/rts/posix/OSMem.c +=================================================================== +--- ghc-8.0.2.orig/rts/posix/OSMem.c ++++ ghc-8.0.2/rts/posix/OSMem.c +@@ -522,11 +522,24 @@ + + #ifdef MADV_FREE + // Try MADV_FREE first, FreeBSD has both and MADV_DONTNEED +- // just swaps memory out ++ // just swaps memory out. Linux >= 4.5 has both DONTNEED and FREE; either ++ // will work as they both allow the system to free anonymous pages. ++ // It is important that we try both methods as the kernel which we were ++ // built on may differ from the kernel we are now running on. + r = madvise(at, size, MADV_FREE); +-#else +- r = madvise(at, size, MADV_DONTNEED); ++ if(r < 0) { ++ if (errno == EINVAL) { ++ // Perhaps the system doesn't support MADV_FREE; fall-through and ++ // try MADV_DONTNEED. ++ } else { ++ sysErrorBelch("unable to decommit memory"); ++ } ++ } else { ++ return; ++ } + #endif ++ ++ r = madvise(at, size, MADV_DONTNEED); + if(r < 0) + sysErrorBelch("unable to decommit memory"); + } diff --git a/ghc-Debian-reproducible-tmp-names.patch b/ghc-Debian-reproducible-tmp-names.patch index e1950ee..16ffc32 100644 --- a/ghc-Debian-reproducible-tmp-names.patch +++ b/ghc-Debian-reproducible-tmp-names.patch @@ -4,19 +4,19 @@ up in the resulting binary (in the debug section), but not the directory. Instead of using the process id, create a hash from the command line arguments, and assume that is going to be unique. -Index: ghc/compiler/main/SysTools.hs +Index: ghc-8.0.2/compiler/main/SysTools.hs =================================================================== ---- ghc.orig/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100 -+++ ghc/compiler/main/SysTools.hs 2015-11-02 17:23:05.410365013 +0100 -@@ -66,6 +66,7 @@ +--- ghc-8.0.2.orig/compiler/main/SysTools.hs ++++ ghc-8.0.2/compiler/main/SysTools.hs +@@ -65,6 +65,7 @@ import Util import DynFlags import Exception +import Fingerprint - import Data.IORef - import Control.Monad -@@ -1152,8 +1153,8 @@ + import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion) + +@@ -1145,8 +1146,8 @@ mapping <- readIORef dir_ref case Map.lookup tmp_dir mapping of Nothing -> do @@ -27,7 +27,7 @@ Index: ghc/compiler/main/SysTools.hs mask_ $ mkTempDir prefix Just dir -> return dir where -@@ -1531,6 +1532,13 @@ +@@ -1562,6 +1563,13 @@ getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral #endif diff --git a/ghc-Debian-x32-use-native-x86_64-insn.patch b/ghc-Debian-x32-use-native-x86_64-insn.patch new file mode 100644 index 0000000..6105b5b --- /dev/null +++ b/ghc-Debian-x32-use-native-x86_64-insn.patch @@ -0,0 +1,27 @@ +Description: Use native x86_64 instructions on x32 + This patch enables a few native 64-bit integer instructions + on x32 which are available on this architecture despite using + 32-bit pointers. These instructions are present on x86_64 but + not on x86 and ghc checks the size of (void *) to determine + that. This method fails on x32 since despite using 32-bit + pointers and hence sizeof(void *) == 4, it still uses the + full x86_64 instruction set and software-emulated variants + of the aforementioned 64-bit integer instructions are + therefore not present in the toolchain which will make ghc + fail to build on x32. + See: https://ghc.haskell.org/trac/ghc/ticket/11571 + . + +Index: ghc-8.0.2/rts/RtsSymbols.c +=================================================================== +--- ghc-8.0.2.orig/rts/RtsSymbols.c ++++ ghc-8.0.2/rts/RtsSymbols.c +@@ -857,7 +857,7 @@ + + + // 64-bit support functions in libgcc.a +-#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) ++#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) && !(defined(__x86_64__) && defined(__ILP32__)) + #define RTS_LIBGCC_SYMBOLS \ + SymI_NeedsProto(__divdi3) \ + SymI_NeedsProto(__udivdi3) \ diff --git a/ghc.spec b/ghc.spec index a19fdbd..3500fb2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ # To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 +%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -14,59 +14,39 @@ Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 7.10.3 +Version: 8.0.2 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 55%{?dist} +Release: 56%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport URL: https://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-src.tar.xz +Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}b-testsuite.tar.xz +Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch -# Debian patch -Patch22: ghc-armv7-VFPv3D16--NEON.patch -Patch23: ghc-7.8.3-Cabal-install-PATH-warning.patch +Patch2: ghc-7.8.3-Cabal-install-PATH-warning.patch +Patch3: ghc-8.0.2-Cabal-dynlibdir.patch + +Patch12: ghc-armv7-VFPv3D16--NEON.patch + +# Debian patches: Patch24: ghc-Debian-buildpath-abi-stability.patch Patch26: ghc-Debian-no-missing-haddock-file-warning.patch Patch27: ghc-Debian-reproducible-tmp-names.patch +Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch +Patch29: ghc-Debian-osdecommitmemory-compat.patch -# 7.10.3 needs llvm-3.5 -%global llvm_major 3.5 - -# use "./libraries-versions.sh" to check versions -%global Cabal_ver 1.22.5.0 -%global array_ver 0.5.1.0 -%global base_ver 4.8.2.0 -%global bin_package_db_ver 0.0.0.0 -%global binary_ver 0.7.5.0 -%global bytestring_ver 0.10.6.0 -%global containers_ver 0.5.6.2 -%global deepseq_ver 1.4.1.1 -%global directory_ver 1.2.2.0 -%global filepath_ver 1.4.0.0 -%global ghc_prim_ver 0.4.0.0 -%global haskeline_ver 0.7.2.1 -%global hoopl_ver 3.10.0.2 -%global hpc_ver 0.6.0.2 -%global integer_gmp_ver 1.0.0.0 -%global pretty_ver 1.1.2.0 -%global process_ver 1.2.3.0 -%global template_haskell_ver 2.10.0.0 -%global terminfo_ver 0.4.0.1 -%global time_ver 1.5.0.1 -%global transformers_ver 0.4.2.0 -%global unix_ver 2.7.1.0 -%global xhtml_ver 3000.2.1 +# 8.0 needs llvm-3.7 +%global llvm_major 3.7 # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -91,15 +71,17 @@ BuildRequires: libffi-devel BuildRequires: ncurses-devel # for man and docs BuildRequires: perl -BuildRequires: libxslt, docbook-style-xsl %if %{undefined without_testsuite} BuildRequires: python %endif -%ifarch armv7hl armv5tel -BuildRequires: llvm35 +%if %{undefined without_manual} +BuildRequires: python-sphinx %endif -%ifarch armv7hl -# patch22 +%ifarch armv7hl aarch64 +BuildRequires: llvm%{llvm_major} +%endif +%ifarch armv7hl aarch64 +# patch12 BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} @@ -145,8 +127,8 @@ Obsoletes: ghc-doc < 6.12.3-4 %if %{defined without_haddock} Obsoletes: ghc-doc-index < %{version}-%{release} %endif -%ifarch armv7hl armv5tel -Requires: llvm35 +%ifarch armv7hl aarch64 +Requires: llvm%{llvm_major} %endif %description compiler @@ -183,36 +165,36 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} +# use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d Cabal-%{Cabal_ver} -%ghc_lib_subpackage -d -l %BSDHaskellReport array-%{array_ver} -%define ghc_pkg_obsoletes ghc-haskell98-devel <= 2.0.0.3, ghc-haskell2010-devel <= 1.1.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} -%undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -d binary-%{binary_ver} -%ghc_lib_subpackage -d bytestring-%{bytestring_ver} -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-%{containers_ver} -%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-%{deepseq_ver} -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-%{directory_ver} -%ghc_lib_subpackage -d filepath-%{filepath_ver} +%ghc_lib_subpackage -d Cabal-1.24.2.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.1.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.9.1.0 +%ghc_lib_subpackage -d binary-0.8.3.0 +%ghc_lib_subpackage -d bytestring-0.10.8.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.7.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.2.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.0 +%ghc_lib_subpackage -d filepath-1.4.1.1 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -d haskeline-%{haskeline_ver} -%ghc_lib_subpackage -d hoopl-%{hoopl_ver} -%ghc_lib_subpackage -d hpc-%{hpc_ver} -%ghc_lib_subpackage -d pretty-%{pretty_ver} -%define ghc_pkg_obsoletes ghc-process-leksah-devel < 1.0.1.4-14 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-%{process_ver} -%undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -d template-haskell-%{template_haskell_ver} -%ghc_lib_subpackage -d -c ncurses-devel%{?_isa} terminfo-%{terminfo_ver} -%ghc_lib_subpackage -d time-%{time_ver} -%ghc_lib_subpackage -d transformers-%{transformers_ver} -%ghc_lib_subpackage -d unix-%{unix_ver} +%ghc_lib_subpackage -d ghc-boot-%{ghc_version_override} +%ghc_lib_subpackage -d ghc-boot-th-%{ghc_version_override} +%ghc_lib_subpackage -d -x ghci-%{ghc_version_override} +%ghc_lib_subpackage -d haskeline-0.7.3.0 +%ghc_lib_subpackage -d hoopl-3.10.2.1 +%ghc_lib_subpackage -d hpc-0.6.0.3 +%ghc_lib_subpackage -d pretty-1.1.3.3 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.4.3.0 +%ghc_lib_subpackage -d template-haskell-2.11.1.0 +%ghc_lib_subpackage -d -c ncurses-devel%{?_isa} terminfo-0.4.0.2 +%ghc_lib_subpackage -d time-1.6.0.1 +%ghc_lib_subpackage -d transformers-0.5.2.0 +%ghc_lib_subpackage -d unix-2.7.2.1 %if %{undefined without_haddock} -%ghc_lib_subpackage -d xhtml-%{xhtml_ver} +%ghc_lib_subpackage -d xhtml-3000.2.1 %endif %endif @@ -238,22 +220,24 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %prep %setup -q -n %{name}-%{version} %{!?without_testsuite:-b1} -# gen_contents_index: use absolute path for haddock %patch1 -p1 -b .orig +%patch2 -p1 -b .orig +%patch3 -p1 -b .orig + %if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs %endif %ifarch armv7hl -%patch22 -p1 -b .orig +%patch12 -p1 -b .orig %endif -%patch23 -p1 -b .orig %patch24 -p1 -b .orig - %patch26 -p1 -b .orig %patch27 -p1 -b .orig +%patch28 -p1 -b .orig +%patch29 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -263,22 +247,19 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then fi %endif -mv libraries/integer-gmp{,.old} -ln -s integer-gmp2 libraries/integer-gmp - %build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF %if %{undefined ghc_bootstrapping} -%ifarch armv7hl armv5tel +%ifarch armv7hl aarch64 BuildFlavour = perf-llvm %else BuildFlavour = perf %endif %else -%ifarch armv7hl armv5tel +%ifarch armv7hl aarch64 BuildFlavour = quick-llvm %else BuildFlavour = quick @@ -288,25 +269,38 @@ GhcLibWays = v dyn %{!?without_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif -%if %{defined without_manual} -BUILD_DOCBOOK_HTML = NO +EXTRA_HADDOCK_OPTS += --hyperlinked-source +%if %{undefined without_manual} +BUILD_MAN = yes +%else +BUILD_MAN = no %endif +BUILD_SPHINX_PDF=no +EOF ## for verbose build output #GhcStage1HcOpts=-v4 ## enable RTS debugging: ## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) #EXTRA_HC_OPTS=-debug -EOF -%ifarch armv7hl +%ifarch armv7hl aarch64 autoreconf %endif + +# still happens when bootstrapping 8.0 with 7.10: # x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC # aarch64: /usr/bin/ld: /usr/lib64/ghc-7.6.3/libHSrts.a(RtsFlags.o)(.text+0x578): unresolvable R_AARCH64_ADR_PREL_PG_HI21 relocation against symbol `stdout@@GLIBC_2.17' %ifarch x86_64 armv7hl aarch64 s390x ppc64 ppc64le %global _hardened_ldflags %{nil} %endif + +%ifnarch aarch64 ppc64 ppc64le export CFLAGS="${CFLAGS:-%optflags}" +%else +%if %{undefined ghc_bootstrapping} +export CFLAGS="${CFLAGS:-%optflags}" +%endif +%endif export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" # * %%configure induces cross-build due to different target/host/build platform names # * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping @@ -315,7 +309,7 @@ export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc \ + --with-gcc=%{_bindir}/gcc --docdir=%{_docdir}/ghc \ --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %if 0%{?fedora} || 0%{?rhel} > 6 --with-system-libffi \ @@ -340,10 +334,10 @@ done # ghc-base should own ghclibdir echo "%%dir %{ghclibdir}" >> ghc-base.files -%ghc_gen_filelists bin-package-db %{bin_package_db_ver} %ghc_gen_filelists ghc %{ghc_version_override} -%ghc_gen_filelists ghc-prim %{ghc_prim_ver} -%ghc_gen_filelists integer-gmp %{integer_gmp_ver} +%ghc_gen_filelists ghci %{ghc_version_override} +%ghc_gen_filelists ghc-prim 0.5.0.0 +%ghc_gen_filelists integer-gmp 1.0.0.1 %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ @@ -353,7 +347,6 @@ echo "%%license libraries/LICENSE.%1" >> ghc-%2.files %merge_filelist integer-gmp base %merge_filelist ghc-prim base -%merge_filelist bin-package-db ghc # add rts libs echo "%%dir %{ghclibdir}/rts" >> ghc-base.files @@ -364,7 +357,7 @@ ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files sed -i -e "s|^%{buildroot}||g" ghc-base.files -ls -d %{buildroot}%{ghclibdir}/rts/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/builtin_*.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files +ls -d %{buildroot}%{ghclibdir}/rts/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files %endif @@ -493,11 +486,16 @@ fi %{ghclibdir}/bin/ghc-pkg %{ghclibdir}/bin/hpc %{ghclibdir}/bin/hsc2hs +%{ghclibdir}/bin/ghc-iserv +%{ghclibdir}/bin/ghc-iserv-dyn +%if %{undefined without_prof} +%{ghclibdir}/bin/ghc-iserv-prof +%endif %{ghclibdir}/bin/runghc -# unknown (unregisterized) archs -%ifnarch ppc64 s390 s390x ppc64le %{mips} aarch64 -%{ghclibdir}/ghc-split +%ifnarch s390 s390x aarch64 %{mips} +%{ghclibdir}/bin/ghc-split %endif +%{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt %dir %{ghclibdir}/package.conf.d @@ -505,8 +503,6 @@ fi %{ghclibdir}/platformConstants %{ghclibdir}/settings %{ghclibdir}/template-hsc.h -%{ghclibdir}/unlit -%{_mandir}/man1/ghc.* %dir %{_docdir}/ghc %dir %{ghc_html_dir} %if %{undefined without_haddock} @@ -517,13 +513,14 @@ fi %{ghclibdir}/html %{ghclibdir}/latex %if %{undefined without_manual} +# https://ghc.haskell.org/trac/ghc/ticket/12939 +#%{_mandir}/man1/ghc.* ## needs pandoc #%%{ghc_html_dir}/Cabal %{ghc_html_dir}/haddock %{ghc_html_dir}/users_guide %endif %dir %{ghc_html_dir}/libraries -%{ghc_html_dir}/libraries/frames.html %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/hslogo-16.png %{ghc_html_dir}/libraries/ocean.css @@ -547,6 +544,13 @@ fi %changelog +* Fri Feb 17 2017 Jens Petersen - 8.0.2-56 +- update to GHC 8.0 (bootstrap build) +- backport changes from http://github.com/fedora-haskell/ghc + adding some new patches from Debian +- use llvm3.7 on ARM archs +- user guide now built with sphinx + * Mon Feb 13 2017 Jens Petersen - 7.10.3-55 - use new ghc_lib_subpackage -d option to fix handling of .files - configure llc-3.5 and opt-3.5 explicitly for all arch's diff --git a/sources b/sources index bf52373..219f0fc 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -d614735d9dac67432f8c6df7e45c76f7 ghc-7.10.3b-src.tar.xz -a2df2aaf3424127f0811c42d386c079b ghc-7.10.3b-testsuite.tar.xz +SHA512 (ghc-8.0.2-src.tar.xz) = 58ea3853cd93b556ecdc4abd0be079b2621171b8491f59004ea4e036a4cba4470aaafe6591b942e0a50a64bdc47540e01fe6900212a1ef7087850112d9bfc5ef +SHA512 (ghc-8.0.2-testsuite.tar.xz) = 1b35fc6a5f482dc1e33f21ddf4c4fe17591990f16a4105c787225980a5f4dbaa42205204faf547f8e1b53f6356aefde9d3ff50cc416c9bf1a9ac08feadd74a99 From 9675f1deeb6fc8e9600a554b1c908149a8df452e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Feb 2017 16:43:39 +0900 Subject: [PATCH 435/530] add ghc-8.0.2/ to .gitignore --- .gitignore | 1 + 1 file changed, 1 insertion(+) diff --git a/.gitignore b/.gitignore index bf56600..bd8cf43 100644 --- a/.gitignore +++ b/.gitignore @@ -22,3 +22,4 @@ testsuite-6.12.3.tar.bz2 /ghc-7.10.3b-testsuite.tar.xz /ghc-8.0.2-testsuite.tar.xz /ghc-8.0.2-src.tar.xz +/ghc-8.0.2/ From edda7ff23d56883f285d2161c933a41866d9e52a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Feb 2017 21:52:47 +0900 Subject: [PATCH 436/530] 8.0.2 perf build --- ghc.spec | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3500fb2..6e8a2d5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ # To bootstrap build a new version of ghc, uncomment the following: -%global ghc_bootstrapping 1 +#%%global ghc_bootstrapping 1 %if %{defined ghc_bootstrapping} %global without_testsuite 1 @@ -20,7 +20,7 @@ Version: 8.0.2 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 56%{?dist} +Release: 57%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -544,6 +544,11 @@ fi %changelog +* Fri Feb 17 2017 Jens Petersen - 8.0.2-57 +- 8.0.2 perf build +- http://downloads.haskell.org/~ghc/8.0.2/docs/html/users_guide/8.0.1-notes.html +- http://downloads.haskell.org/~ghc/8.0.2/docs/html/users_guide/8.0.2-notes.html + * Fri Feb 17 2017 Jens Petersen - 8.0.2-56 - update to GHC 8.0 (bootstrap build) - backport changes from http://github.com/fedora-haskell/ghc From 43c46ce3583603bcc51a7a6df23342402cb3d3a6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 18 Feb 2017 00:35:18 +0900 Subject: [PATCH 437/530] fix ABI check for uninstalled package (which may be redundant now) ghc-xhtml is not built for bootstrap, so check was failing --- ghc.spec | 16 ++++++++++------ 1 file changed, 10 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6e8a2d5..e4bba12 100644 --- a/ghc.spec +++ b/ghc.spec @@ -422,13 +422,17 @@ make test echo "Checking package ABI hashes:" for i in %{ghc_packages_list}; do old=$(ghc-pkg field $i id --simple-output) - new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) - if [ "$old" != "$new" ]; then - echo "ABI hash for $i changed!:" >&2 - echo " $old -> $new" >&2 - ghc_abi_hash_change=yes + if [ -n "$old" ]; then + new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) + if [ "$old" != "$new" ]; then + echo "ABI hash for $i changed!:" >&2 + echo " $old -> $new" >&2 + ghc_abi_hash_change=yes + else + echo "($old unchanged)" + fi else - echo "($old unchanged)" + echo "($i not installed)" fi done if [ "$ghc_abi_hash_change" = "yes" ]; then From 5430a62a8de21db02bdc28b2ee31d833837b5ff4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 18 Feb 2017 07:15:15 +0900 Subject: [PATCH 438/530] do not fail id (ABI) check if package uninstalled --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index e4bba12..7046a6a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -421,7 +421,7 @@ make test %if %{undefined ghc_bootstrapping} echo "Checking package ABI hashes:" for i in %{ghc_packages_list}; do - old=$(ghc-pkg field $i id --simple-output) + old=$(ghc-pkg field $i id --simple-output || :) if [ -n "$old" ]; then new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) if [ "$old" != "$new" ]; then From 40266e57f28c3884c74273769e7ac030ca7cb266 Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Petr=20P=C3=ADsa=C5=99?= Date: Wed, 12 Jul 2017 14:16:12 +0200 Subject: [PATCH 439/530] perl dependency renamed to perl-interpreter --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 7046a6a..36a6e24 100644 --- a/ghc.spec +++ b/ghc.spec @@ -70,7 +70,7 @@ BuildRequires: libffi-devel # for terminfo BuildRequires: ncurses-devel # for man and docs -BuildRequires: perl +BuildRequires: perl-interpreter %if %{undefined without_testsuite} BuildRequires: python %endif From b613b3dce5014902e8854bc2135c9e88fdf2154b Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Wed, 26 Jul 2017 09:30:47 +0000 Subject: [PATCH 440/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 36a6e24..d330d0f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,7 +20,7 @@ Version: 8.0.2 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 57%{?dist} +Release: 58%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -548,6 +548,9 @@ fi %changelog +* Wed Jul 26 2017 Fedora Release Engineering - 8.0.2-58 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Mass_Rebuild + * Fri Feb 17 2017 Jens Petersen - 8.0.2-57 - 8.0.2 perf build - http://downloads.haskell.org/~ghc/8.0.2/docs/html/users_guide/8.0.1-notes.html From b1bcda66be44d0f09bce2933516a83ec53432cfe Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Wed, 2 Aug 2017 21:09:08 +0000 Subject: [PATCH 441/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Binutils_Mass_Rebuild --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d330d0f..204140b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -20,7 +20,7 @@ Version: 8.0.2 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 58%{?dist} +Release: 59%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -548,6 +548,9 @@ fi %changelog +* Wed Aug 02 2017 Fedora Release Engineering - 8.0.2-59 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Binutils_Mass_Rebuild + * Wed Jul 26 2017 Fedora Release Engineering - 8.0.2-58 - Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Mass_Rebuild From 69183c7357a954f58d99bd3f1d884186bf382eb6 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Mar 2017 11:19:44 +0900 Subject: [PATCH 442/530] exclude ghc-boot from ghc-libraries but ghc-boot-th should be there for TH --- ghc.spec | 3 ++- libraries-versions.sh | 2 +- 2 files changed, 3 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 204140b..4ea70d0 100644 --- a/ghc.spec +++ b/ghc.spec @@ -180,7 +180,7 @@ documention. # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -d ghc-boot-%{ghc_version_override} +%ghc_lib_subpackage -d -x ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -x ghci-%{ghc_version_override} %ghc_lib_subpackage -d haskeline-0.7.3.0 @@ -334,6 +334,7 @@ done # ghc-base should own ghclibdir echo "%%dir %{ghclibdir}" >> ghc-base.files +%ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} %ghc_gen_filelists ghc-prim 0.5.0.0 diff --git a/libraries-versions.sh b/libraries-versions.sh index 4b51e27..ff78e57 100755 --- a/libraries-versions.sh +++ b/libraries-versions.sh @@ -7,4 +7,4 @@ fi cd libraries -grep -i ^version: Cabal/Cabal/Cabal.cabal */*.cabal | grep -v -e "\(Win32\|gmp.old\|gmp2\|integer-simple\|ghc-boot\)" | sed -e "s!/.*: \+!_ver !" +grep -i ^version: Cabal/Cabal/Cabal.cabal */*.cabal | grep -v -e "\(Win32\|gmp.old\|gmp2\|integer-simple\)" | sed -e "s!/.*: \+!-!" From 029c355c71157af57dc4628af724331783026d53 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 26 Oct 2017 20:19:54 +0900 Subject: [PATCH 443/530] fix space %BSDHaskellReport macro for rpm-4.14 --- ghc.spec | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4ea70d0..2477498 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,8 +9,7 @@ #%%undefine without_haddock %endif -%global space %(echo -n ' ') -%global BSDHaskellReport BSD%{space}and%{space}HaskellReport +%global BSDHaskellReport %{quote:BSD and HaskellReport} Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems @@ -20,7 +19,7 @@ Version: 8.0.2 # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically # xhtml has not had a new release for some years -Release: 59%{?dist} +Release: 60%{?dist} Summary: Glasgow Haskell Compiler License: %BSDHaskellReport @@ -549,6 +548,10 @@ fi %changelog +* Thu Oct 26 2017 Jens Petersen - 8.0.2-60 +- fix space in BSDHaskellReport license macro for rpm-4.14 +- drop ghc-boot from ghc-libraries + * Wed Aug 02 2017 Fedora Release Engineering - 8.0.2-59 - Rebuilt for https://fedoraproject.org/wiki/Fedora_27_Binutils_Mass_Rebuild From 353b1aabc8bdb33927e9592a5a4d412324e53112 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 26 Oct 2017 23:17:19 +0900 Subject: [PATCH 444/530] more license fields cleanup put in explicit BSD's and only use %quote for macros args --- ghc.spec | 42 +++++++++++++++++++++--------------------- 1 file changed, 21 insertions(+), 21 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2477498..cd33ba9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -9,8 +9,6 @@ #%%undefine without_haddock %endif -%global BSDHaskellReport %{quote:BSD and HaskellReport} - Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems Version: 8.0.2 @@ -22,7 +20,7 @@ Version: 8.0.2 Release: 60%{?dist} Summary: Glasgow Haskell Compiler -License: %BSDHaskellReport +License: BSD and HaskellReport URL: https://haskell.org/ghc/ Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} @@ -164,36 +162,38 @@ documention. %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} +%global BSDHaskellReport %{quote:BSD and HaskellReport} + # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d Cabal-1.24.2.0 +%ghc_lib_subpackage -d -l BSD Cabal-1.24.2.0 %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.1.1 %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.9.1.0 -%ghc_lib_subpackage -d binary-0.8.3.0 -%ghc_lib_subpackage -d bytestring-0.10.8.1 +%ghc_lib_subpackage -d -l BSD binary-0.8.3.0 +%ghc_lib_subpackage -d -l BSD bytestring-0.10.8.1 %ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.7.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.2.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.0 -%ghc_lib_subpackage -d filepath-1.4.1.1 +%ghc_lib_subpackage -d -l BSD filepath-1.4.1.1 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes -%ghc_lib_subpackage -d -x ghc-boot-%{ghc_version_override} -%ghc_lib_subpackage -d ghc-boot-th-%{ghc_version_override} -%ghc_lib_subpackage -d -x ghci-%{ghc_version_override} -%ghc_lib_subpackage -d haskeline-0.7.3.0 -%ghc_lib_subpackage -d hoopl-3.10.2.1 -%ghc_lib_subpackage -d hpc-0.6.0.3 -%ghc_lib_subpackage -d pretty-1.1.3.3 +%ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} +%ghc_lib_subpackage -d -x -l BSD ghci-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD haskeline-0.7.3.0 +%ghc_lib_subpackage -d -l BSD hoopl-3.10.2.1 +%ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 +%ghc_lib_subpackage -d -l BSD pretty-1.1.3.3 %ghc_lib_subpackage -d -l %BSDHaskellReport process-1.4.3.0 -%ghc_lib_subpackage -d template-haskell-2.11.1.0 -%ghc_lib_subpackage -d -c ncurses-devel%{?_isa} terminfo-0.4.0.2 -%ghc_lib_subpackage -d time-1.6.0.1 -%ghc_lib_subpackage -d transformers-0.5.2.0 -%ghc_lib_subpackage -d unix-2.7.2.1 +%ghc_lib_subpackage -d -l BSD template-haskell-2.11.1.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.0.2 +%ghc_lib_subpackage -d -l BSD time-1.6.0.1 +%ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 +%ghc_lib_subpackage -d -l BSD unix-2.7.2.1 %if %{undefined without_haddock} -%ghc_lib_subpackage -d xhtml-3000.2.1 +%ghc_lib_subpackage -d -l BSD xhtml-3000.2.1 %endif %endif @@ -201,7 +201,7 @@ documention. %package libraries Summary: GHC development libraries meta package -License: %BSDHaskellReport +License: BSD and HaskellReport Requires: ghc-compiler = %{version}-%{release} Obsoletes: ghc-devel < %{version}-%{release} Provides: ghc-devel = %{version}-%{release} From 0b28d2d4326f766546237af78aaa76583562bf05 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 26 Oct 2017 23:24:17 +0900 Subject: [PATCH 445/530] mark other subpackages correctly as BSD license --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index cd33ba9..ea59561 100644 --- a/ghc.spec +++ b/ghc.spec @@ -550,6 +550,7 @@ fi %changelog * Thu Oct 26 2017 Jens Petersen - 8.0.2-60 - fix space in BSDHaskellReport license macro for rpm-4.14 +- mark other subpackages correctly as BSD license - drop ghc-boot from ghc-libraries * Wed Aug 02 2017 Fedora Release Engineering - 8.0.2-59 From 3d07439f6fab86406c7d4015eb067ba90f7381c7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 27 Oct 2017 13:59:40 +0900 Subject: [PATCH 446/530] update source urls to the ones they redirected to --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index ea59561..2831ab4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,9 +22,9 @@ Summary: Glasgow Haskell Compiler License: BSD and HaskellReport URL: https://haskell.org/ghc/ -Source0: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-src.tar.xz +Source0: https://downloads.haskell.org/~ghc/dist/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} -Source1: http://www.haskell.org/ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz +Source1: https://downloads.haskell.org/~ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index From 261695ad42048ceff2d87a3c4edab477bd888236 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 22 Nov 2017 15:23:53 +0530 Subject: [PATCH 447/530] correct source url --- ghc.spec | 4 ++-- 1 file changed, 2 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2831ab4..5ec1faa 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,9 +22,9 @@ Summary: Glasgow Haskell Compiler License: BSD and HaskellReport URL: https://haskell.org/ghc/ -Source0: https://downloads.haskell.org/~ghc/dist/%{version}/ghc-%{version}-src.tar.xz +Source0: https://downloads.haskell.org/~ghc/%{version}/ghc-%{version}-src.tar.xz %if %{undefined without_testsuite} -Source1: https://downloads.haskell.org/~ghc/dist/%{version}/ghc-%{version}-testsuite.tar.xz +Source1: https://downloads.haskell.org/~ghc/%{version}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index From 49e998df53402714f6b933db38fbb7e873c085a2 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 28 Dec 2017 17:41:20 +0100 Subject: [PATCH 448/530] python2 and comment out %mandir properly --- ghc.spec | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 5ec1faa..be3e7e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -69,10 +69,10 @@ BuildRequires: ncurses-devel # for man and docs BuildRequires: perl-interpreter %if %{undefined without_testsuite} -BuildRequires: python +BuildRequires: python2 %endif %if %{undefined without_manual} -BuildRequires: python-sphinx +BuildRequires: python2-sphinx %endif %ifarch armv7hl aarch64 BuildRequires: llvm%{llvm_major} @@ -518,7 +518,7 @@ fi %{ghclibdir}/latex %if %{undefined without_manual} # https://ghc.haskell.org/trac/ghc/ticket/12939 -#%{_mandir}/man1/ghc.* +#%%{_mandir}/man1/ghc.* ## needs pandoc #%%{ghc_html_dir}/Cabal %{ghc_html_dir}/haddock From 3e04bbc620fda95a28d4a01262e61fcf62b6d341 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jan 2018 00:12:56 +0100 Subject: [PATCH 449/530] update to 8.2.2: backport from fedora-haskell/ghc bootstrap build --- .gitignore | 1 + ghc-7.8.3-Cabal-install-PATH-warning.patch | 12 -- ghc-8.0.2-Cabal-dynlibdir.patch | 11 -- ghc-Cabal-install-PATH-warning.patch | 20 +++ ghc-Debian-osdecommitmemory-compat.patch | 39 ----- ghc.spec | 171 ++++++++++++--------- shadowed-deps.patch | 13 ++ sources | 3 +- 8 files changed, 136 insertions(+), 134 deletions(-) delete mode 100644 ghc-7.8.3-Cabal-install-PATH-warning.patch delete mode 100644 ghc-8.0.2-Cabal-dynlibdir.patch create mode 100644 ghc-Cabal-install-PATH-warning.patch delete mode 100644 ghc-Debian-osdecommitmemory-compat.patch create mode 100644 shadowed-deps.patch diff --git a/.gitignore b/.gitignore index bd8cf43..71eaaa4 100644 --- a/.gitignore +++ b/.gitignore @@ -23,3 +23,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.0.2-testsuite.tar.xz /ghc-8.0.2-src.tar.xz /ghc-8.0.2/ +/ghc-8.2.2-src.tar.xz diff --git a/ghc-7.8.3-Cabal-install-PATH-warning.patch b/ghc-7.8.3-Cabal-install-PATH-warning.patch deleted file mode 100644 index e7ef6e1..0000000 --- a/ghc-7.8.3-Cabal-install-PATH-warning.patch +++ /dev/null @@ -1,12 +0,0 @@ ---- ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2014-07-10 13:34:21.000000000 +0900 -+++ ghc-7.8.3/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2014-08-29 16:48:12.621694879 +0900 -@@ -148,8 +148,7 @@ - notice verbosity ("Installing executable(s) in " ++ binPref) - inPath <- isInSearchPath binPref - when (not inPath) $ -- warn verbosity ("The directory " ++ binPref -- ++ " is not in the system search path.") -+ warn verbosity ("Executable installed in " ++ binPref) - - -- install include files for all compilers - they may be needed to compile - -- haskell files (using the CPP extension) diff --git a/ghc-8.0.2-Cabal-dynlibdir.patch b/ghc-8.0.2-Cabal-dynlibdir.patch deleted file mode 100644 index 3f55fa3..0000000 --- a/ghc-8.0.2-Cabal-dynlibdir.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-8.0.1.20161117/libraries/Cabal/Cabal/Distribution/Simple/InstallDirs.hs~ 2016-11-18 07:08:46.000000000 +0900 -+++ ghc-8.0.1.20161117/libraries/Cabal/Cabal/Distribution/Simple/InstallDirs.hs 2016-12-07 18:19:02.670468156 +0900 -@@ -186,7 +186,7 @@ - JHC -> "$compiler" - LHC -> "$compiler" - UHC -> "$pkgid" -- _other -> "$abi", -+ _other -> "$compiler/$pkgkey", - libexecdir = case buildOS of - Windows -> "$prefix" "$libname" - _other -> "$prefix" "libexec", diff --git a/ghc-Cabal-install-PATH-warning.patch b/ghc-Cabal-install-PATH-warning.patch new file mode 100644 index 0000000..5081fa1 --- /dev/null +++ b/ghc-Cabal-install-PATH-warning.patch @@ -0,0 +1,20 @@ +--- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 16:51:43.000000000 +0200 ++++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-01-23 23:05:47.047081056 +0100 +@@ -36,7 +36,7 @@ + import Distribution.Simple.Utils + ( createDirectoryIfMissingVerbose + , installDirectoryContents, installOrdinaryFile, isInSearchPath +- , die', info, noticeNoWrap, warn, matchDirFileGlob ) ++ , die', info, noticeNoWrap, warn, matchDirFileGlob, debug ) + import Distribution.Simple.Compiler + ( CompilerFlavor(..), compilerFlavor ) + import Distribution.Simple.Setup +@@ -215,7 +215,7 @@ + ++ " in " ++ binPref) + inPath <- isInSearchPath binPref + when (not inPath) $ +- warn verbosity ("The directory " ++ binPref ++ debug verbosity ("The directory " ++ binPref + ++ " is not in the system search path.") + case compilerFlavor (compiler lbi) of + GHC -> GHC.installExe verbosity lbi binPref buildPref progFix pkg_descr exe diff --git a/ghc-Debian-osdecommitmemory-compat.patch b/ghc-Debian-osdecommitmemory-compat.patch deleted file mode 100644 index 2c84d94..0000000 --- a/ghc-Debian-osdecommitmemory-compat.patch +++ /dev/null @@ -1,39 +0,0 @@ -Description: rts: Ensure we always give MADV_DONTNEED a chance in osDecommitMemory -Author: Ben Gamari -Origin: upstream, https://phabricator.haskell.org/D2780 -Bug: https://ghc.haskell.org/trac/ghc/ticket/12865 -Bug-Debian: https://bugs.debian.org/847677 ---- -This patch header follows DEP-3: http://dep.debian.net/deps/dep3/ -Index: ghc-8.0.2/rts/posix/OSMem.c -=================================================================== ---- ghc-8.0.2.orig/rts/posix/OSMem.c -+++ ghc-8.0.2/rts/posix/OSMem.c -@@ -522,11 +522,24 @@ - - #ifdef MADV_FREE - // Try MADV_FREE first, FreeBSD has both and MADV_DONTNEED -- // just swaps memory out -+ // just swaps memory out. Linux >= 4.5 has both DONTNEED and FREE; either -+ // will work as they both allow the system to free anonymous pages. -+ // It is important that we try both methods as the kernel which we were -+ // built on may differ from the kernel we are now running on. - r = madvise(at, size, MADV_FREE); --#else -- r = madvise(at, size, MADV_DONTNEED); -+ if(r < 0) { -+ if (errno == EINVAL) { -+ // Perhaps the system doesn't support MADV_FREE; fall-through and -+ // try MADV_DONTNEED. -+ } else { -+ sysErrorBelch("unable to decommit memory"); -+ } -+ } else { -+ return; -+ } - #endif -+ -+ r = madvise(at, size, MADV_DONTNEED); - if(r < 0) - sysErrorBelch("unable to decommit memory"); - } diff --git a/ghc.spec b/ghc.spec index be3e7e2..91e2c66 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,61 +1,67 @@ -# To bootstrap build a new version of ghc, uncomment the following: -#%%global ghc_bootstrapping 1 +# To bootstrap build a new version of ghc, comment out this line: +#%%global perf_build 1 -%if %{defined ghc_bootstrapping} -%global without_testsuite 1 -%global without_prof 1 +# to handle RCs +%global ghc_release 8.2.2 + +%if %{undefined perf_build} +%bcond_with testsuite +%bcond_with prof %{?ghc_bootstrap} ### uncomment to generate haddocks for bootstrap #%%undefine without_haddock +%else +%bcond_without testsuite +%bcond_without prof %endif Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 8.0.2 +Version: 8.2.2 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -# xhtml has not had a new release for some years -Release: 60%{?dist} +Release: 61%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport URL: https://haskell.org/ghc/ -Source0: https://downloads.haskell.org/~ghc/%{version}/ghc-%{version}-src.tar.xz -%if %{undefined without_testsuite} -Source1: https://downloads.haskell.org/~ghc/%{version}/ghc-%{version}-testsuite.tar.xz +Source0: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-src.tar.xz +%if %{with testsuite} +Source1: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-testsuite.tar.xz %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch -Patch2: ghc-7.8.3-Cabal-install-PATH-warning.patch -Patch3: ghc-8.0.2-Cabal-dynlibdir.patch +Patch2: ghc-Cabal-install-PATH-warning.patch +# https://github.com/haskell/cabal/issues/4728 +Patch4: https://gist.githubusercontent.com/expipiplus1/6720ebc3db90f36031d651ca2e6507c4/raw/b330b21457628dc7088236a000b4a0f16d109665/shadowed-deps.patch Patch12: ghc-armv7-VFPv3D16--NEON.patch # Debian patches: -Patch24: ghc-Debian-buildpath-abi-stability.patch +# doesn't apply to 8.2 +#Patch24: ghc-Debian-buildpath-abi-stability.patch Patch26: ghc-Debian-no-missing-haddock-file-warning.patch Patch27: ghc-Debian-reproducible-tmp-names.patch Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch -Patch29: ghc-Debian-osdecommitmemory-compat.patch -# 8.0 needs llvm-3.7 -%global llvm_major 3.7 +# 8.2 needs llvm-3.9 +%global llvm_major 3.9 # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel # see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -%if %{undefined ghc_bootstrapping} +%if %{defined perf_build} BuildRequires: ghc-compiler = %{version} # for ABI hash checking BuildRequires: ghc = %{version} %endif -BuildRequires: ghc-rpm-macros-extra >= 1.6.15 +BuildRequires: ghc-rpm-macros-extra >= 1.8 BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel @@ -68,11 +74,11 @@ BuildRequires: libffi-devel BuildRequires: ncurses-devel # for man and docs BuildRequires: perl-interpreter -%if %{undefined without_testsuite} -BuildRequires: python2 +%if %{with testsuite} +BuildRequires: python3 %endif %if %{undefined without_manual} -BuildRequires: python2-sphinx +BuildRequires: python3-sphinx %endif %ifarch armv7hl aarch64 BuildRequires: llvm%{llvm_major} @@ -166,34 +172,35 @@ documention. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-1.24.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.1.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.9.1.0 -%ghc_lib_subpackage -d -l BSD binary-0.8.3.0 -%ghc_lib_subpackage -d -l BSD bytestring-0.10.8.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.7.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.0 -%ghc_lib_subpackage -d -l BSD filepath-1.4.1.1 +%ghc_lib_subpackage -d -l BSD Cabal-2.0.1.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.2.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.10.1.0 +%ghc_lib_subpackage -d -l BSD binary-0.8.5.1 +%ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.10.2 +%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.3.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.2 +%ghc_lib_subpackage -d -l BSD filepath-1.4.1.2 %define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} %undefine ghc_pkg_obsoletes %ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} -%ghc_lib_subpackage -d -x -l BSD ghci-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD haskeline-0.7.3.0 -%ghc_lib_subpackage -d -l BSD hoopl-3.10.2.1 +%ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 +%ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.0 +%ghc_lib_subpackage -d -l BSD hoopl-3.10.2.2 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.3 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.4.3.0 -%ghc_lib_subpackage -d -l BSD template-haskell-2.11.1.0 -%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.0.2 -%ghc_lib_subpackage -d -l BSD time-1.6.0.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.1.0 +%ghc_lib_subpackage -d -l BSD template-haskell-2.12.0.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.0 +%ghc_lib_subpackage -d -l BSD time-1.8.0.2 %ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 -%ghc_lib_subpackage -d -l BSD unix-2.7.2.1 +%ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{undefined without_haddock} -%ghc_lib_subpackage -d -l BSD xhtml-3000.2.1 +%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2 %endif %endif @@ -217,12 +224,12 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %prep -%setup -q -n %{name}-%{version} %{!?without_testsuite:-b1} +%setup -q -n %{name}-%{version} %{?with_testsuite:-b1} %patch1 -p1 -b .orig %patch2 -p1 -b .orig -%patch3 -p1 -b .orig +%patch4 -p1 -b .orig %if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs @@ -232,11 +239,10 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif -%patch24 -p1 -b .orig +#%%patch24 -p1 -b .orig %patch26 -p1 -b .orig %patch27 -p1 -b .orig %patch28 -p1 -b .orig -%patch29 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{undefined without_haddock} @@ -251,7 +257,7 @@ fi # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF -%if %{undefined ghc_bootstrapping} +%if %{defined perf_build} %ifarch armv7hl aarch64 BuildFlavour = perf-llvm %else @@ -264,7 +270,7 @@ BuildFlavour = quick-llvm BuildFlavour = quick %endif %endif -GhcLibWays = v dyn %{!?without_prof:p} +GhcLibWays = v dyn %{?with_prof:p} %if %{defined without_haddock} HADDOCK_DOCS = NO %endif @@ -286,29 +292,27 @@ EOF autoreconf %endif -# still happens when bootstrapping 8.0 with 7.10: -# x86_64: /usr/bin/ld: utils/ghc-pwd/dist-boot/Main.o: relocation R_X86_64_32S against `.text' can not be used when making a shared object; recompile with -fPIC -# aarch64: /usr/bin/ld: /usr/lib64/ghc-7.6.3/libHSrts.a(RtsFlags.o)(.text+0x578): unresolvable R_AARCH64_ADR_PREL_PG_HI21 relocation against symbol `stdout@@GLIBC_2.17' -%ifarch x86_64 armv7hl aarch64 s390x ppc64 ppc64le -%global _hardened_ldflags %{nil} -%endif - -%ifnarch aarch64 ppc64 ppc64le -export CFLAGS="${CFLAGS:-%optflags}" +%if 0%{?fedora} > 28 +%ghc_set_cflags %else -%if %{undefined ghc_bootstrapping} -export CFLAGS="${CFLAGS:-%optflags}" +# -Wunused-label is extremely noisy +%ifarch aarch64 s390x +CFLAGS="${CFLAGS:-$(echo %optflags | sed -e 's/-Wall -Werror=format-security //')}" +%else +CFLAGS="${CFLAGS:-%optflags}" %endif +export CFLAGS %endif export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" +# for ghc-8.2 +export CC=%{_bindir}/gcc # * %%configure induces cross-build due to different target/host/build platform names -# * --with-gcc=%{_bindir}/gcc is to avoid ccache hardcoding problem when bootstrapping ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ --datadir=%{_datadir} --includedir=%{_includedir} --libdir=%{_libdir} \ --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ - --with-gcc=%{_bindir}/gcc --docdir=%{_docdir}/ghc \ + --docdir=%{_docdir}/ghc \ --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %if 0%{?fedora} || 0%{?rhel} > 6 --with-system-libffi \ @@ -323,41 +327,59 @@ make %{?_smp_mflags} %install make DESTDIR=%{buildroot} install +mv %{buildroot}%{ghclibdir}/*/libHS*ghc%{ghc_version}.so %{buildroot}%{_libdir}/ +for i in $(find %{buildroot} -type f -exec sh -c "file {} | grep -q 'dynamically linked'" \; -print); do + chrpath -d $i +done + +for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do + sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_libdir}!' $i +done + for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver +%if 0%{?rhel} && 0%{?rhel} < 8 +echo "%%doc libraries/$name/LICENSE" >> ghc-$name.files +%else echo "%%license libraries/$name/LICENSE" >> ghc-$name.files +%endif done # ghc-base should own ghclibdir -echo "%%dir %{ghclibdir}" >> ghc-base.files +echo "%%dir %{ghclibdir}" >> ghc-base-devel.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.5.0.0 -%ghc_gen_filelists integer-gmp 1.0.0.1 +%ghc_gen_filelists ghc-prim 0.5.1.1 +%ghc_gen_filelists integer-gmp 1.0.1.0 %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ -echo "%%license libraries/LICENSE.%1" >> ghc-%2.files +%if 0%{?rhel} && 0%{?rhel} < 8\ +echo "%%doc libraries/LICENSE.%1" >> ghc-%2.files\ +%else\ +echo "%%license libraries/LICENSE.%1" >> ghc-%2.files\ +%endif %merge_filelist integer-gmp base %merge_filelist ghc-prim base # add rts libs -echo "%%dir %{ghclibdir}/rts" >> ghc-base.files -ls %{buildroot}%{ghclibdir}/rts/libHS*.so >> ghc-base.files +echo "%{ghclibdir}/rts" >> ghc-base-devel.files +ls %{buildroot}%{_libdir}/libHSrts*.so >> ghc-base.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files %endif +sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf sed -i -e "s|^%{buildroot}||g" ghc-base.files -ls -d %{buildroot}%{ghclibdir}/rts/lib*.a %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files +ls -d %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files %endif @@ -413,12 +435,12 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if %{undefined without_testsuite} +%if %{with testsuite} make test %endif # check the ABI hashes -%if %{undefined ghc_bootstrapping} +%if %{defined perf_build} echo "Checking package ABI hashes:" for i in %{ghc_packages_list}; do old=$(ghc-pkg field $i id --simple-output || :) @@ -492,18 +514,20 @@ fi %{ghclibdir}/bin/hsc2hs %{ghclibdir}/bin/ghc-iserv %{ghclibdir}/bin/ghc-iserv-dyn -%if %{undefined without_prof} +%if %{with prof} %{ghclibdir}/bin/ghc-iserv-prof %endif %{ghclibdir}/bin/runghc -%ifnarch s390 s390x aarch64 %{mips} +%ifnarch s390 s390x %{mips} %{ghclibdir}/bin/ghc-split %endif +%{ghclibdir}/bin/hp2ps %{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache +%{ghclibdir}/package.conf.d/package.cache.lock %{ghclibdir}/platformConstants %{ghclibdir}/settings %{ghclibdir}/template-hsc.h @@ -548,6 +572,13 @@ fi %changelog +* Wed Jan 24 2018 Jens Petersen - 8.2.2-61 +- 8.2.2 bootstrap build +- install ghc libs in libdir and remove RUNPATHs +- add shadowed-deps.patch (haskell/cabal#4728) +- new ghc-compact library +- exclude ghc-boot for ghc-libraries + * Thu Oct 26 2017 Jens Petersen - 8.0.2-60 - fix space in BSDHaskellReport license macro for rpm-4.14 - mark other subpackages correctly as BSD license diff --git a/shadowed-deps.patch b/shadowed-deps.patch new file mode 100644 index 0000000..faa5db0 --- /dev/null +++ b/shadowed-deps.patch @@ -0,0 +1,13 @@ +diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs +index 949cc0f231..408794e078 100644 +--- a/compiler/main/Packages.hs ++++ b/compiler/main/Packages.hs +@@ -1339,7 +1339,7 @@ validateDatabase dflags pkg_map1 = + unusable = directly_ignored `Map.union` unusable_ignored + `Map.union` unusable_broken + `Map.union` unusable_cyclic +- `Map.union` unusable_shadowed ++ -- `Map.union` unusable_shadowed + + -- ----------------------------------------------------------------------------- + -- When all the command-line options are in, we can process our package diff --git a/sources b/sources index 219f0fc..9fd240d 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -SHA512 (ghc-8.0.2-src.tar.xz) = 58ea3853cd93b556ecdc4abd0be079b2621171b8491f59004ea4e036a4cba4470aaafe6591b942e0a50a64bdc47540e01fe6900212a1ef7087850112d9bfc5ef -SHA512 (ghc-8.0.2-testsuite.tar.xz) = 1b35fc6a5f482dc1e33f21ddf4c4fe17591990f16a4105c787225980a5f4dbaa42205204faf547f8e1b53f6356aefde9d3ff50cc416c9bf1a9ac08feadd74a99 +SHA512 (ghc-8.2.2-src.tar.xz) = 6549416f470b599973d409fa45f59c25b07e6a94798cef1a19ad432547dc225338cf4dbc4a4793114b4a417798a3b59b122b92b020251074405c5302b7ffe799 From a8a36662bcdba5bd5f98e3b63dfc92df2c0d5c51 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jan 2018 18:34:47 +0100 Subject: [PATCH 450/530] 8.2.2 perf build --- ghc.spec | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 91e2c66..3eadd69 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ # To bootstrap build a new version of ghc, comment out this line: -#%%global perf_build 1 +%global perf_build 1 # to handle RCs %global ghc_release 8.2.2 @@ -22,7 +22,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 61%{?dist} +Release: 62%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -572,6 +572,11 @@ fi %changelog +* Thu Jan 25 2018 Jens Petersen - 8.2.2-62 +- 8.2.2 perf build +- https://downloads.haskell.org/~ghc/8.2.2/docs/html/users_guide/8.2.1-notes.html +- https://downloads.haskell.org/~ghc/8.2.2/docs/html/users_guide/8.2.2-notes.html + * Wed Jan 24 2018 Jens Petersen - 8.2.2-61 - 8.2.2 bootstrap build - install ghc libs in libdir and remove RUNPATHs From 4735cadb517b3050baea36f5d9be2e24b315ea2f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 24 Jan 2018 18:45:50 +0100 Subject: [PATCH 451/530] add 8.2.2 testsuite tarball --- .gitignore | 1 + sources | 1 + 2 files changed, 2 insertions(+) diff --git a/.gitignore b/.gitignore index 71eaaa4..8ced83f 100644 --- a/.gitignore +++ b/.gitignore @@ -24,3 +24,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.0.2-src.tar.xz /ghc-8.0.2/ /ghc-8.2.2-src.tar.xz +/ghc-8.2.2-testsuite.tar.xz diff --git a/sources b/sources index 9fd240d..6b499bd 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ SHA512 (ghc-8.2.2-src.tar.xz) = 6549416f470b599973d409fa45f59c25b07e6a94798cef1a19ad432547dc225338cf4dbc4a4793114b4a417798a3b59b122b92b020251074405c5302b7ffe799 +SHA512 (ghc-8.2.2-testsuite.tar.xz) = 5b60413910bce2ef0d71e2f531d7297cefc0b03df3e23d63f7a872d9a264e1512b2d6631a3fba35e72d113389762ba34d503649ea4a852ce9fd42e94ef6b96dc From 2cf8aee77c2682bb70e17851fe2a93945a76dc88 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 30 Jan 2018 00:58:52 +0100 Subject: [PATCH 452/530] upstream patch under review in Phabricator to workaround shadow hash issue https://ghc.haskell.org/trac/ghc/ticket/14381 --- D4159.patch | 214 ++++++++++++++++++++++++++++++++++++++++++++ ghc.spec | 9 +- shadowed-deps.patch | 13 --- 3 files changed, 221 insertions(+), 15 deletions(-) create mode 100644 D4159.patch delete mode 100644 shadowed-deps.patch diff --git a/D4159.patch b/D4159.patch new file mode 100644 index 0000000..86599e9 --- /dev/null +++ b/D4159.patch @@ -0,0 +1,214 @@ +diff --git a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout +--- a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout ++++ b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout +@@ -1,6 +1,11 @@ ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages + Preprocessing library 'p' for bkpcabal01-0.1.0.0.. + Building library 'p' instantiated with H = + for bkpcabal01-0.1.0.0.. ++ignoring (possibly broken) abi-depends field for packages + Preprocessing library 'q' for bkpcabal01-0.1.0.0.. + Building library 'q' instantiated with H = + for bkpcabal01-0.1.0.0.. ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages +diff --git a/testsuite/tests/cabal/T12485a.stdout b/testsuite/tests/cabal/T12485a.stdout +--- a/testsuite/tests/cabal/T12485a.stdout ++++ b/testsuite/tests/cabal/T12485a.stdout +@@ -1,3 +1,4 @@ ++ignoring (possibly broken) abi-depends field for packages + should SUCCEED + should SUCCEED + should SUCCEED +diff --git a/testsuite/tests/cabal/T5442d.stdout b/testsuite/tests/cabal/T5442d.stdout +--- a/testsuite/tests/cabal/T5442d.stdout ++++ b/testsuite/tests/cabal/T5442d.stdout +@@ -1,6 +1,7 @@ + Reading package info from "shadow1.pkg" ... done. + Reading package info from "shadow4.pkg" ... done. + Reading package info from "shadow2.pkg" ... done. ++ignoring (possibly broken) abi-depends field for packages + global (should be empty): + user: + shadow-2 +diff --git a/testsuite/tests/cabal/cabal01/cabal01.stdout b/testsuite/tests/cabal/cabal01/cabal01.stdout +--- a/testsuite/tests/cabal/cabal01/cabal01.stdout ++++ b/testsuite/tests/cabal/cabal01/cabal01.stdout +@@ -1,3 +1,4 @@ ++ignoring (possibly broken) abi-depends field for packages + install1: + bin + lib +diff --git a/testsuite/tests/cabal/cabal06/cabal06.stdout b/testsuite/tests/cabal/cabal06/cabal06.stdout +--- a/testsuite/tests/cabal/cabal06/cabal06.stdout ++++ b/testsuite/tests/cabal/cabal06/cabal06.stdout +@@ -1,3 +1,7 @@ ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages + Does the first instance of q depend on p-1.0? + 1 + Does the second instance of q depend on p-1.0? +diff --git a/testsuite/tests/cabal/cabal08/cabal08.stdout b/testsuite/tests/cabal/cabal08/cabal08.stdout +--- a/testsuite/tests/cabal/cabal08/cabal08.stdout ++++ b/testsuite/tests/cabal/cabal08/cabal08.stdout +@@ -1,3 +1,5 @@ ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages + [1 of 1] Compiling Main ( Main.hs, Main.o ) + Linking Main ... + p2 +diff --git a/testsuite/tests/cabal/shadow.stdout b/testsuite/tests/cabal/shadow.stdout +--- a/testsuite/tests/cabal/shadow.stdout ++++ b/testsuite/tests/cabal/shadow.stdout +@@ -1,3 +1,4 @@ ++ignoring (possibly broken) abi-depends field for packages + databases 1 and 2: + localshadow1.package.conf + (shadow-1) +diff --git a/testsuite/tests/driver/recomp007/recomp007.stdout b/testsuite/tests/driver/recomp007/recomp007.stdout +--- a/testsuite/tests/driver/recomp007/recomp007.stdout ++++ b/testsuite/tests/driver/recomp007/recomp007.stdout +@@ -1,3 +1,5 @@ ++ignoring (possibly broken) abi-depends field for packages ++ignoring (possibly broken) abi-depends field for packages + Preprocessing executable 'test' for b-1.0.. + Building executable 'test' for b-1.0.. + [1 of 2] Compiling B ( B.hs, dist/build/test/test-tmp/B.o ) [A changed] +diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +--- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout ++++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout +@@ -1,49 +1,53 @@ ++ignoring (possibly broken) abi-depends field for packages + pdb.safePkg01/local.db + safePkg01-1.0 + + trusted: False + + M_SafePkg +-package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: safe + require own pkg trusted: False + + M_SafePkg2 +-package dependencies: base-4.9.0.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: base-4.11.0.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: trustworthy + require own pkg trusted: False + + M_SafePkg3 +-package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: safe + require own pkg trusted: True + + M_SafePkg4 +-package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: safe + require own pkg trusted: True + + M_SafePkg5 +-package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: safe + require own pkg trusted: True + + M_SafePkg6 +-package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: array-0.5.2.0 base-4.11.0.0* bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: trustworthy + require own pkg trusted: False + + M_SafePkg7 +-package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: array-0.5.2.0 base-4.11.0.0* bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: safe + require own pkg trusted: False + + M_SafePkg8 +-package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 ++package dependencies: array-0.5.2.0 base-4.11.0.0 bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 + trusted: trustworthy + require own pkg trusted: False + + Testing setting trust ++ignoring (possibly broken) abi-depends field for packages + trusted: True ++ignoring (possibly broken) abi-depends field for packages + trusted: False ++ignoring (possibly broken) abi-depends field for packages + trusted: False +diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs +--- a/utils/ghc-pkg/Main.hs ++++ b/utils/ghc-pkg/Main.hs +@@ -1208,7 +1208,18 @@ + pkgsCabalFormat = packages db + + pkgsGhcCacheFormat :: [PackageCacheFormat] +- pkgsGhcCacheFormat = map convertPackageInfoToCacheFormat pkgsCabalFormat ++ pkgsGhcCacheFormat ++ = map (recomputeValidAbiDeps pkgsCabalFormat) -- Note [Recompute abi-depends] ++ $ map convertPackageInfoToCacheFormat ++ pkgsCabalFormat ++ ++ hasAnyAbiDepends :: InstalledPackageInfo -> Bool ++ hasAnyAbiDepends x = length (abiDepends x) > 0 ++ ++ -- warn when we find any (possibly-)bogus abi-depends fields; ++ -- Note [Recompute abi-depends] ++ when (any hasAnyAbiDepends pkgsCabalFormat) $ ++ infoLn "ignoring (possibly broken) abi-depends field for packages" + + when (verbosity > Normal) $ + infoLn ("writing cache " ++ filename) +@@ -1231,6 +1242,45 @@ + ModuleName + OpenModule + ++{- Note [Recompute abi-depends] ++~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ ++ ++Like most fields, `ghc-pkg` relies on who-ever is performing package ++registration to fill in fields; this includes the `abi-depends` field present ++for the package. ++ ++However, this was likely a mistake, and is not very robust; in certain cases, ++versions of Cabal may use bogus abi-depends fields for a package when doing ++builds. Why? Because package database information is aggressively cached; it is ++possible to work Cabal into a situation where it uses a cached version of ++`abi-depends`, rather than the one in the actual database after it has been ++recomputed. ++ ++However, there is an easy fix: ghc-pkg /already/ knows the `abi-depends` of a ++package, because they are the ABIs of the packages pointed at by the `depends` ++field. So it can simply look up the abi from the dependencies in the original ++database, and ignore whatever the system registering gave it. ++ ++So, instead, we do two things here: ++ ++ - We throw away the information for a registered package's `abi-depends` field. ++ ++ - We recompute it: we simply look up the unit ID of the package in the original ++ database, and use *its* abi-depends. ++ ++See Trac #14381, and Cabal issue #4728. ++ ++-} ++ ++recomputeValidAbiDeps :: [InstalledPackageInfo] -> PackageCacheFormat -> PackageCacheFormat ++recomputeValidAbiDeps db pkg = pkg { GhcPkg.abiDepends = catMaybes (newAbiDeps) } ++ where ++ newAbiDeps = flip map (GhcPkg.abiDepends pkg) $ \(k, _) -> ++ case filter (\d -> installedUnitId d == k) db of ++ [] -> Nothing ++ [x] -> Just (k, unAbiHash (abiHash x)) ++ _ -> Nothing -- ??? ++ + convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat + convertPackageInfoToCacheFormat pkg = + GhcPkg.InstalledPackageInfo { + diff --git a/ghc.spec b/ghc.spec index 3eadd69..a30c4f6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 62%{?dist} +Release: 63%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -37,7 +37,8 @@ Source4: ghc-doc-index Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch # https://github.com/haskell/cabal/issues/4728 -Patch4: https://gist.githubusercontent.com/expipiplus1/6720ebc3db90f36031d651ca2e6507c4/raw/b330b21457628dc7088236a000b4a0f16d109665/shadowed-deps.patch +# https://ghc.haskell.org/trac/ghc/ticket/14381 +Patch4: https://phabricator-files.haskell.org/file/data/pgrn3b7lw22ccodkc4nf/PHID-FILE-o3pkv37yfa5h2q3xflrd/D4159.patch Patch12: ghc-armv7-VFPv3D16--NEON.patch @@ -572,6 +573,10 @@ fi %changelog +* Tue Jan 30 2018 Jens Petersen - 8.2.2-63 +- apply Phabricator D4159.patch to workaround + https://ghc.haskell.org/trac/ghc/ticket/14381 + * Thu Jan 25 2018 Jens Petersen - 8.2.2-62 - 8.2.2 perf build - https://downloads.haskell.org/~ghc/8.2.2/docs/html/users_guide/8.2.1-notes.html diff --git a/shadowed-deps.patch b/shadowed-deps.patch deleted file mode 100644 index faa5db0..0000000 --- a/shadowed-deps.patch +++ /dev/null @@ -1,13 +0,0 @@ -diff --git a/compiler/main/Packages.hs b/compiler/main/Packages.hs -index 949cc0f231..408794e078 100644 ---- a/compiler/main/Packages.hs -+++ b/compiler/main/Packages.hs -@@ -1339,7 +1339,7 @@ validateDatabase dflags pkg_map1 = - unusable = directly_ignored `Map.union` unusable_ignored - `Map.union` unusable_broken - `Map.union` unusable_cyclic -- `Map.union` unusable_shadowed -+ -- `Map.union` unusable_shadowed - - -- ----------------------------------------------------------------------------- - -- When all the command-line options are in, we can process our package From a98b38e9ff8314aa45f505a7622412b2fdf0b4bc Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Wed, 7 Feb 2018 11:11:05 +0000 Subject: [PATCH 453/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_28_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a30c4f6..be6cf11 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 63%{?dist} +Release: 64%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -573,6 +573,9 @@ fi %changelog +* Wed Feb 07 2018 Fedora Release Engineering - 8.2.2-64 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_28_Mass_Rebuild + * Tue Jan 30 2018 Jens Petersen - 8.2.2-63 - apply Phabricator D4159.patch to workaround https://ghc.haskell.org/trac/ghc/ticket/14381 From 90d0a342655eb44ecd66fd266c47670aa26639e3 Mon Sep 17 00:00:00 2001 From: Igor Gnatenko Date: Fri, 9 Feb 2018 09:04:35 +0100 Subject: [PATCH 454/530] Escape macros in %changelog Reference: https://lists.fedoraproject.org/archives/list/devel@lists.fedoraproject.org/thread/Y2ZUKK2B7T2IKXPMODNF6HB2O5T5TS6H/ Signed-off-by: Igor Gnatenko --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index be6cf11..bf73fba 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 64%{?dist} +Release: 65%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -573,6 +573,9 @@ fi %changelog +* Fri Feb 09 2018 Igor Gnatenko - 8.2.2-65 +- Escape macros in %%changelog + * Wed Feb 07 2018 Fedora Release Engineering - 8.2.2-64 - Rebuilt for https://fedoraproject.org/wiki/Fedora_28_Mass_Rebuild @@ -1191,7 +1194,7 @@ fi - try to install man pages * Thu Nov 12 2009 Bryan O'Sullivan - 6.12.0.20091010-3 -- fix %check +- fix %%check * Sun Oct 11 2009 Bryan O'Sullivan - 6.12.0.20091010-2 - disable ppc for now (seems unsupported) From 21da3237866adb25a4eb6245d25122222f0e04a9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 May 2018 22:36:35 +0900 Subject: [PATCH 455/530] ghost ghc-doc-index local state and more libraries index files --- ghc.spec | 18 +++++++++++++----- 1 file changed, 13 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index bf73fba..a64c104 100644 --- a/ghc.spec +++ b/ghc.spec @@ -22,7 +22,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 65%{?dist} +Release: 66%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -414,6 +414,8 @@ cd .. # we package the library license files separately find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';' +touch %{buildroot}%{_localstatedir}/lib/ghc/pkg-dir.cache{,.new} + %check export LANG=en_US.utf8 @@ -551,28 +553,34 @@ fi %endif %dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index -%{ghc_html_dir}/libraries/hslogo-16.png -%{ghc_html_dir}/libraries/ocean.css %{ghc_html_dir}/libraries/prologue.txt -%{ghc_html_dir}/libraries/synopsis.png %{ghc_html_dir}/index.html %ghost %{ghc_html_dir}/libraries/doc-index*.html %ghost %{ghc_html_dir}/libraries/haddock-util.js +%ghost %{ghc_html_dir}/libraries/hslogo-16.png %ghost %{ghc_html_dir}/libraries/index*.html %ghost %{ghc_html_dir}/libraries/minus.gif +%ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif -%{_localstatedir}/lib/ghc +%ghost %{ghc_html_dir}/libraries/synopsis.png %endif %if %{undefined without_haddock} %files doc-index %config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index +%dir %{_localstatedir}/lib/ghc +%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache +%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache.new %endif %files libraries %changelog +* Wed May 2 2018 Jens Petersen - 8.2.2-66 +- ghost the ghc-doc-index local state files +- ghost some newer libraries index files + * Fri Feb 09 2018 Igor Gnatenko - 8.2.2-65 - Escape macros in %%changelog From 2cf7cd1707ec6f21fd7a772196e6347eecca3ede Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 2 May 2018 22:38:48 +0900 Subject: [PATCH 456/530] move manuals to ghc-doc package again after a long break... --- ghc.spec | 31 ++++++++++++++++++++++++------- 1 file changed, 24 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index a64c104..1d5fba5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -89,6 +89,9 @@ BuildRequires: llvm%{llvm_major} BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} +%if %{undefined without_manual} +Requires: ghc-doc = %{version}-%{release} +%endif %if %{undefined without_haddock} Requires: ghc-doc-index = %{version}-%{release} %endif @@ -126,8 +129,6 @@ Requires: ghc-base-devel%{?_isa} # for alternatives Requires(post): chkconfig Requires(postun): chkconfig -# added in f14 -Obsoletes: ghc-doc < 6.12.3-4 %if %{defined without_haddock} Obsoletes: ghc-doc-index < %{version}-%{release} %endif @@ -143,12 +144,23 @@ To install all of ghc (including the ghc library), install the main ghc package. +%if %{undefined without_manual} +%package doc +Summary: GHC documentation +License: BSD +BuildArch: noarch + +%description doc +This package provides the User Guide and Haddock manual. +%endif + %if %{undefined without_haddock} %package doc-index Summary: GHC library development documentation indexing License: BSD Requires: ghc-compiler = %{version}-%{release} Requires: crontabs +BuildArch: noarch %description doc-index The package provides a cronjob for re-indexing installed library development @@ -546,15 +558,10 @@ fi %if %{undefined without_manual} # https://ghc.haskell.org/trac/ghc/ticket/12939 #%%{_mandir}/man1/ghc.* -## needs pandoc -#%%{ghc_html_dir}/Cabal -%{ghc_html_dir}/haddock -%{ghc_html_dir}/users_guide %endif %dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/prologue.txt -%{ghc_html_dir}/index.html %ghost %{ghc_html_dir}/libraries/doc-index*.html %ghost %{ghc_html_dir}/libraries/haddock-util.js %ghost %{ghc_html_dir}/libraries/hslogo-16.png @@ -565,6 +572,15 @@ fi %ghost %{ghc_html_dir}/libraries/synopsis.png %endif +%if %{undefined without_manual} +%files doc +## needs pandoc +#%%{ghc_html_dir}/Cabal +%{ghc_html_dir}/haddock +%{ghc_html_dir}/index.html +%{ghc_html_dir}/users_guide +%endif + %if %{undefined without_haddock} %files doc-index %config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index @@ -578,6 +594,7 @@ fi %changelog * Wed May 2 2018 Jens Petersen - 8.2.2-66 +- move manuals to ghc-doc - ghost the ghc-doc-index local state files - ghost some newer libraries index files From 00d0db7f76da4d75d3ed547dc5700ccb163215d7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 3 May 2018 00:52:51 +0900 Subject: [PATCH 457/530] silence the ghc-pkg abi-depends warnings when installing packages forward-port from f28 branch --- D4159.patch | 152 ++-------------------------------------------------- ghc.spec | 5 +- 2 files changed, 8 insertions(+), 149 deletions(-) diff --git a/D4159.patch b/D4159.patch index 86599e9..45e646a 100644 --- a/D4159.patch +++ b/D4159.patch @@ -1,147 +1,3 @@ -diff --git a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout ---- a/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout -+++ b/testsuite/tests/backpack/cabal/bkpcabal02/bkpcabal02.stdout -@@ -1,6 +1,11 @@ -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages - Preprocessing library 'p' for bkpcabal01-0.1.0.0.. - Building library 'p' instantiated with H = - for bkpcabal01-0.1.0.0.. -+ignoring (possibly broken) abi-depends field for packages - Preprocessing library 'q' for bkpcabal01-0.1.0.0.. - Building library 'q' instantiated with H = - for bkpcabal01-0.1.0.0.. -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages -diff --git a/testsuite/tests/cabal/T12485a.stdout b/testsuite/tests/cabal/T12485a.stdout ---- a/testsuite/tests/cabal/T12485a.stdout -+++ b/testsuite/tests/cabal/T12485a.stdout -@@ -1,3 +1,4 @@ -+ignoring (possibly broken) abi-depends field for packages - should SUCCEED - should SUCCEED - should SUCCEED -diff --git a/testsuite/tests/cabal/T5442d.stdout b/testsuite/tests/cabal/T5442d.stdout ---- a/testsuite/tests/cabal/T5442d.stdout -+++ b/testsuite/tests/cabal/T5442d.stdout -@@ -1,6 +1,7 @@ - Reading package info from "shadow1.pkg" ... done. - Reading package info from "shadow4.pkg" ... done. - Reading package info from "shadow2.pkg" ... done. -+ignoring (possibly broken) abi-depends field for packages - global (should be empty): - user: - shadow-2 -diff --git a/testsuite/tests/cabal/cabal01/cabal01.stdout b/testsuite/tests/cabal/cabal01/cabal01.stdout ---- a/testsuite/tests/cabal/cabal01/cabal01.stdout -+++ b/testsuite/tests/cabal/cabal01/cabal01.stdout -@@ -1,3 +1,4 @@ -+ignoring (possibly broken) abi-depends field for packages - install1: - bin - lib -diff --git a/testsuite/tests/cabal/cabal06/cabal06.stdout b/testsuite/tests/cabal/cabal06/cabal06.stdout ---- a/testsuite/tests/cabal/cabal06/cabal06.stdout -+++ b/testsuite/tests/cabal/cabal06/cabal06.stdout -@@ -1,3 +1,7 @@ -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages - Does the first instance of q depend on p-1.0? - 1 - Does the second instance of q depend on p-1.0? -diff --git a/testsuite/tests/cabal/cabal08/cabal08.stdout b/testsuite/tests/cabal/cabal08/cabal08.stdout ---- a/testsuite/tests/cabal/cabal08/cabal08.stdout -+++ b/testsuite/tests/cabal/cabal08/cabal08.stdout -@@ -1,3 +1,5 @@ -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages - [1 of 1] Compiling Main ( Main.hs, Main.o ) - Linking Main ... - p2 -diff --git a/testsuite/tests/cabal/shadow.stdout b/testsuite/tests/cabal/shadow.stdout ---- a/testsuite/tests/cabal/shadow.stdout -+++ b/testsuite/tests/cabal/shadow.stdout -@@ -1,3 +1,4 @@ -+ignoring (possibly broken) abi-depends field for packages - databases 1 and 2: - localshadow1.package.conf - (shadow-1) -diff --git a/testsuite/tests/driver/recomp007/recomp007.stdout b/testsuite/tests/driver/recomp007/recomp007.stdout ---- a/testsuite/tests/driver/recomp007/recomp007.stdout -+++ b/testsuite/tests/driver/recomp007/recomp007.stdout -@@ -1,3 +1,5 @@ -+ignoring (possibly broken) abi-depends field for packages -+ignoring (possibly broken) abi-depends field for packages - Preprocessing executable 'test' for b-1.0.. - Building executable 'test' for b-1.0.. - [1 of 2] Compiling B ( B.hs, dist/build/test/test-tmp/B.o ) [A changed] -diff --git a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout ---- a/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout -+++ b/testsuite/tests/safeHaskell/check/pkg01/safePkg01.stdout -@@ -1,49 +1,53 @@ -+ignoring (possibly broken) abi-depends field for packages - pdb.safePkg01/local.db - safePkg01-1.0 - - trusted: False - - M_SafePkg --package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: safe - require own pkg trusted: False - - M_SafePkg2 --package dependencies: base-4.9.0.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: base-4.11.0.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: trustworthy - require own pkg trusted: False - - M_SafePkg3 --package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: safe - require own pkg trusted: True - - M_SafePkg4 --package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: safe - require own pkg trusted: True - - M_SafePkg5 --package dependencies: base-4.9.0.0* ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: base-4.11.0.0* ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: safe - require own pkg trusted: True - - M_SafePkg6 --package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: array-0.5.2.0 base-4.11.0.0* bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: trustworthy - require own pkg trusted: False - - M_SafePkg7 --package dependencies: array-0.5.1.0 base-4.9.0.0* bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: array-0.5.2.0 base-4.11.0.0* bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: safe - require own pkg trusted: False - - M_SafePkg8 --package dependencies: array-0.5.1.0 base-4.9.0.0 bytestring-0.10.7.0* deepseq-1.4.2.0 ghc-prim-0.5.0.0 integer-gmp-1.0.0.0 -+package dependencies: array-0.5.2.0 base-4.11.0.0 bytestring-0.10.8.2* deepseq-1.4.3.0 ghc-prim-0.5.2.0 integer-gmp-1.0.1.0 - trusted: trustworthy - require own pkg trusted: False - - Testing setting trust -+ignoring (possibly broken) abi-depends field for packages - trusted: True -+ignoring (possibly broken) abi-depends field for packages - trusted: False -+ignoring (possibly broken) abi-depends field for packages - trusted: False diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs --- a/utils/ghc-pkg/Main.hs +++ b/utils/ghc-pkg/Main.hs @@ -158,10 +14,10 @@ diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs + hasAnyAbiDepends :: InstalledPackageInfo -> Bool + hasAnyAbiDepends x = length (abiDepends x) > 0 + -+ -- warn when we find any (possibly-)bogus abi-depends fields; -+ -- Note [Recompute abi-depends] -+ when (any hasAnyAbiDepends pkgsCabalFormat) $ -+ infoLn "ignoring (possibly broken) abi-depends field for packages" ++-- -- warn when we find any (possibly-)bogus abi-depends fields; ++-- -- Note [Recompute abi-depends] ++-- when (any hasAnyAbiDepends pkgsCabalFormat) $ ++-- infoLn "ignoring (possibly broken) abi-depends field for packages" when (verbosity > Normal) $ infoLn ("writing cache " ++ filename) diff --git a/ghc.spec b/ghc.spec index 1d5fba5..8bceba4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -593,11 +593,14 @@ fi %changelog -* Wed May 2 2018 Jens Petersen - 8.2.2-66 +* Wed May 2 2018 Jens Petersen - 8.2.2-67 - move manuals to ghc-doc - ghost the ghc-doc-index local state files - ghost some newer libraries index files +* Tue Apr 10 2018 Jens Petersen - 8.2.2-66 +- ghc-pkg: silence the abi-depends warnings + * Fri Feb 09 2018 Igor Gnatenko - 8.2.2-65 - Escape macros in %%changelog From 6365edff4552c84a8c587c6a7d97a525e0b4ca48 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 23 May 2018 11:18:05 +0900 Subject: [PATCH 458/530] drop unstable url from D4159.patch and add D4159 url --- ghc.spec | 3 ++- 1 file changed, 2 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8bceba4..a15adeb 100644 --- a/ghc.spec +++ b/ghc.spec @@ -38,7 +38,8 @@ Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch # https://github.com/haskell/cabal/issues/4728 # https://ghc.haskell.org/trac/ghc/ticket/14381 -Patch4: https://phabricator-files.haskell.org/file/data/pgrn3b7lw22ccodkc4nf/PHID-FILE-o3pkv37yfa5h2q3xflrd/D4159.patch +# https://phabricator.haskell.org/D4159 +Patch4: D4159.patch Patch12: ghc-armv7-VFPv3D16--NEON.patch From 6b9498a3c1dc1ed24724878f657a0de704e6d5f1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 28 May 2018 11:58:23 +0900 Subject: [PATCH 459/530] extend and simplify bcond for build configuration - move manuals to ghc-manual.noarch - rename ghc-doc-index to ghc-doc-cron.noarch - drop bootstrap builds and do ABI hash checks unless ghc version changed - no longer need autotools on aarch64 --- D4159.patch | 2 +- ghc.spec | 179 ++++++++++++++++++++++++++++------------------------ 2 files changed, 98 insertions(+), 83 deletions(-) diff --git a/D4159.patch b/D4159.patch index 45e646a..17db2f3 100644 --- a/D4159.patch +++ b/D4159.patch @@ -17,7 +17,7 @@ diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs +-- -- warn when we find any (possibly-)bogus abi-depends fields; +-- -- Note [Recompute abi-depends] +-- when (any hasAnyAbiDepends pkgsCabalFormat) $ -+-- infoLn "ignoring (possibly broken) abi-depends field for packages" ++-- infoLn "ignoring (possibly broken) abi-depends field for packages" when (verbosity > Normal) $ infoLn ("writing cache " ++ filename) diff --git a/ghc.spec b/ghc.spec index a15adeb..98118e9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,19 +1,20 @@ -# To bootstrap build a new version of ghc, comment out this line: -%global perf_build 1 +# perf production build (disable for quick build) +%bcond_without perf_build -# to handle RCs -%global ghc_release 8.2.2 - -%if %{undefined perf_build} -%bcond_with testsuite -%bcond_with prof -%{?ghc_bootstrap} -### uncomment to generate haddocks for bootstrap -#%%undefine without_haddock -%else +# make sure ghc libraries' ABI hashes unchanged +%bcond_without abicheck + +# run testsuite %bcond_without testsuite +# build profiling libraries %bcond_without prof -%endif +# build manual +%bcond_without manual +# build library documentation +%bcond_without haddock + +# to handle RCs +%global ghc_release %{version} Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems @@ -22,7 +23,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 66%{?dist} +Release: 67%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -58,7 +59,7 @@ Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch # and retired arches: alpha sparcv9 armv5tel # see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -%if %{defined perf_build} +%if %{with abicheck} BuildRequires: ghc-compiler = %{version} # for ABI hash checking BuildRequires: ghc = %{version} @@ -79,25 +80,25 @@ BuildRequires: perl-interpreter %if %{with testsuite} BuildRequires: python3 %endif -%if %{undefined without_manual} +%if %{with manual} BuildRequires: python3-sphinx %endif %ifarch armv7hl aarch64 BuildRequires: llvm%{llvm_major} %endif -%ifarch armv7hl aarch64 +%ifarch armv7hl # patch12 BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} -%if %{undefined without_manual} -Requires: ghc-doc = %{version}-%{release} -%endif -%if %{undefined without_haddock} -Requires: ghc-doc-index = %{version}-%{release} +%if %{with haddock} +Requires: ghc-doc-cron = %{version}-%{release} %endif -Requires: ghc-libraries = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} +Requires: ghc-libraries = %{version}-%{release} +%if %{with manual} +Requires: ghc-manual = %{version}-%{release} +%endif %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -130,7 +131,11 @@ Requires: ghc-base-devel%{?_isa} # for alternatives Requires(post): chkconfig Requires(postun): chkconfig -%if %{defined without_haddock} +# added in f14 +Obsoletes: ghc-doc < 6.12.3-4 +%if %{without haddock} +Obsoletes: ghc-doc-cron < %{version}-%{release} +# added in f28 Obsoletes: ghc-doc-index < %{version}-%{release} %endif %ifarch armv7hl aarch64 @@ -145,27 +150,30 @@ To install all of ghc (including the ghc library), install the main ghc package. -%if %{undefined without_manual} -%package doc -Summary: GHC documentation +%if %{with haddock} +%package doc-cron +Summary: GHC library documentation indexing cronjob License: BSD +Requires: ghc-compiler = %{version}-%{release} +Requires: crontabs +# added in f28 +Obsoletes: ghc-doc-index < %{version}-%{release} BuildArch: noarch -%description doc -This package provides the User Guide and Haddock manual. +%description doc-cron +The package provides a cronjob for re-indexing installed library development +documention. %endif -%if %{undefined without_haddock} -%package doc-index -Summary: GHC library development documentation indexing + +%if %{with manual} +%package manual +Summary: GHC manual License: BSD -Requires: ghc-compiler = %{version}-%{release} -Requires: crontabs BuildArch: noarch -%description doc-index -The package provides a cronjob for re-indexing installed library development -documention. +%description manual +This package provides the User Guide and Haddock manual. %endif @@ -213,7 +221,7 @@ documention. %ghc_lib_subpackage -d -l BSD time-1.8.0.2 %ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 -%if %{undefined without_haddock} +%if %{with haddock} %ghc_lib_subpackage -d -l BSD xhtml-3000.2.2 %endif %endif @@ -259,7 +267,7 @@ rm -r libffi-tarballs %patch28 -p1 -b .orig %global gen_contents_index gen_contents_index.orig -%if %{undefined without_haddock} +%if %{with haddock} if [ ! -f "libraries/%{gen_contents_index}" ]; then echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!" exit 1 @@ -271,7 +279,7 @@ fi # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF -%if %{defined perf_build} +%if %{with perf_build} %ifarch armv7hl aarch64 BuildFlavour = perf-llvm %else @@ -285,11 +293,11 @@ BuildFlavour = quick %endif %endif GhcLibWays = v dyn %{?with_prof:p} -%if %{defined without_haddock} +%if %{without haddock} HADDOCK_DOCS = NO %endif EXTRA_HADDOCK_OPTS += --hyperlinked-source -%if %{undefined without_manual} +%if %{with manual} BUILD_MAN = yes %else BUILD_MAN = no @@ -302,7 +310,7 @@ EOF ## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) #EXTRA_HC_OPTS=-debug -%ifarch armv7hl aarch64 +%ifarch armv7hl autoreconf %endif @@ -412,10 +420,11 @@ done %ghc_strip_dynlinked -%if %{undefined without_haddock} +%if %{with haddock} mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p %{buildroot}%{_localstatedir}/lib/ghc +touch %{buildroot}%{_localstatedir}/lib/ghc/pkg-dir.cache{,.new} install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index # generate initial lib doc index @@ -427,8 +436,6 @@ cd .. # we package the library license files separately find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';' -touch %{buildroot}%{_localstatedir}/lib/ghc/pkg-dir.cache{,.new} - %check export LANG=en_US.utf8 @@ -451,34 +458,37 @@ echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* -%if %{with testsuite} -make test -%endif # check the ABI hashes -%if %{defined perf_build} -echo "Checking package ABI hashes:" -for i in %{ghc_packages_list}; do - old=$(ghc-pkg field $i id --simple-output || :) - if [ -n "$old" ]; then - new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) - if [ "$old" != "$new" ]; then - echo "ABI hash for $i changed!:" >&2 - echo " $old -> $new" >&2 - ghc_abi_hash_change=yes +%if %{with abicheck} +if [ "%{version}" = "$(ghc --numeric-version)" ]; then + echo "Checking package ABI hashes:" + for i in %{ghc_packages_list}; do + old=$(ghc-pkg field $i id --simple-output || :) + if [ -n "$old" ]; then + new=$(/usr/lib/rpm/ghc-pkg-wrapper %{buildroot}%{ghclibdir} field $i id --simple-output) + if [ "$old" != "$new" ]; then + echo "ABI hash for $i changed!:" >&2 + echo " $old -> $new" >&2 + ghc_abi_hash_change=yes + else + echo "($old unchanged)" + fi else - echo "($old unchanged)" + echo "($i not installed)" fi - else - echo "($i not installed)" + done + if [ "$ghc_abi_hash_change" = "yes" ]; then + echo "ghc ABI hash change: aborting build!" >&2 + exit 1 fi -done -if [ "$ghc_abi_hash_change" = "yes" ]; then - echo "ghc ABI hash change: aborting build!" >&2 - exit 1 fi %endif +%if %{with testsuite} +make test +%endif + %post compiler # Alas, GHC, Hugs, and nhc all come with different set of tools in @@ -549,14 +559,14 @@ fi %{ghclibdir}/template-hsc.h %dir %{_docdir}/ghc %dir %{ghc_html_dir} -%if %{undefined without_haddock} +%if %{with haddock} %{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} %{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex -%if %{undefined without_manual} +%if %{with manual} # https://ghc.haskell.org/trac/ghc/ticket/12939 #%%{_mandir}/man1/ghc.* %endif @@ -571,10 +581,21 @@ fi %ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif %ghost %{ghc_html_dir}/libraries/synopsis.png +%dir %{_localstatedir}/lib/ghc +%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache +%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache.new %endif -%if %{undefined without_manual} -%files doc +%if %{with haddock} +%files doc-cron +%config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index +%endif + +%files libraries + + +%if %{with manual} +%files manual ## needs pandoc #%%{ghc_html_dir}/Cabal %{ghc_html_dir}/haddock @@ -582,22 +603,16 @@ fi %{ghc_html_dir}/users_guide %endif -%if %{undefined without_haddock} -%files doc-index -%config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index -%dir %{_localstatedir}/lib/ghc -%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache -%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache.new -%endif - -%files libraries - %changelog -* Wed May 2 2018 Jens Petersen - 8.2.2-67 -- move manuals to ghc-doc +* Thu May 24 2018 Jens Petersen - 8.2.2-67 +- move manuals to ghc-manual.noarch +- rename ghc-doc-index to ghc-doc-cron.noarch - ghost the ghc-doc-index local state files - ghost some newer libraries index files +- simplify and extend bcond for build configuration +- drop bootstrap builds and do ABI hash checks unless ghc version changed +- no longer need autotools on aarch64 * Tue Apr 10 2018 Jens Petersen - 8.2.2-66 - ghc-pkg: silence the abi-depends warnings From 92d190083df7f45f68b170c74e0204b32b81c3f3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 28 May 2018 12:44:26 +0900 Subject: [PATCH 460/530] try fixing sphinx-build --version detection in configure https://github.com/ghc/ghc/pull/143 --- ghc-configure-fix-sphinx-version-check.patch | 11 +++++++++++ ghc.spec | 12 +++++++++++- 2 files changed, 22 insertions(+), 1 deletion(-) create mode 100644 ghc-configure-fix-sphinx-version-check.patch diff --git a/ghc-configure-fix-sphinx-version-check.patch b/ghc-configure-fix-sphinx-version-check.patch new file mode 100644 index 0000000..c19da05 --- /dev/null +++ b/ghc-configure-fix-sphinx-version-check.patch @@ -0,0 +1,11 @@ +--- ghc-8.2.2/configure.ac~ 2017-11-21 05:22:42.000000000 +0900 ++++ ghc-8.2.2/configure.ac 2018-05-28 12:37:35.296728423 +0900 +@@ -745,7 +745,7 @@ + AC_CACHE_CHECK([for version of sphinx-build], fp_cv_sphinx_version, + changequote(, )dnl + [if test -n "$SPHINXBUILD"; then +- fp_cv_sphinx_version=`"$SPHINXBUILD" --version 2>&1 | sed 's/Sphinx\( (sphinx-build)\)\? v\?\([0-9]\.[0-9]\.[0-9]\)/\2/' | head -n1`; ++ fp_cv_sphinx_version=`"$SPHINXBUILD" --version 2>&1 | sed 's/.* v\?\([0-9]\.[0-9]\.[0-9]\)/\1/' | head -n1`; + fi; + changequote([, ])dnl + ]) diff --git a/ghc.spec b/ghc.spec index 98118e9..9807eb1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -41,6 +41,8 @@ Patch2: ghc-Cabal-install-PATH-warning.patch # https://ghc.haskell.org/trac/ghc/ticket/14381 # https://phabricator.haskell.org/D4159 Patch4: D4159.patch +# https://github.com/ghc/ghc/pull/143 +Patch5: ghc-configure-fix-sphinx-version-check.patch Patch12: ghc-armv7-VFPv3D16--NEON.patch @@ -81,11 +83,14 @@ BuildRequires: perl-interpreter BuildRequires: python3 %endif %if %{with manual} -BuildRequires: python3-sphinx +# for /usr/bin/sphinx-build +BuildRequires: python2-sphinx %endif %ifarch armv7hl aarch64 BuildRequires: llvm%{llvm_major} %endif +# patch5 +BuildRequires: autoconf %ifarch armv7hl # patch12 BuildRequires: autoconf, automake @@ -252,6 +257,7 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %patch2 -p1 -b .orig %patch4 -p1 -b .orig +%patch5 -p1 -b .orig %if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs @@ -310,8 +316,12 @@ EOF ## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) #EXTRA_HC_OPTS=-debug +# for patch12 %ifarch armv7hl autoreconf +%else +# for patch5 +autoconf %endif %if 0%{?fedora} > 28 From 1eb070f18f0b3d48ae7f76bf843500f5c972e262 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 28 May 2018 20:37:39 +0900 Subject: [PATCH 461/530] merge manual and haddock bcond to docs disabling haddock seems to disable manual anyway https://ghc.haskell.org/trac/ghc/ticket/15190 --- ghc.spec | 45 +++++++++++++++++++++++---------------------- 1 file changed, 23 insertions(+), 22 deletions(-) diff --git a/ghc.spec b/ghc.spec index 9807eb1..b77c1f5 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,10 +8,10 @@ %bcond_without testsuite # build profiling libraries %bcond_without prof -# build manual -%bcond_without manual -# build library documentation -%bcond_without haddock +# build docs (haddock and manuals) +# combined since disabling haddock seems to cause no manuals built +# +%bcond_without docs # to handle RCs %global ghc_release %{version} @@ -82,7 +82,7 @@ BuildRequires: perl-interpreter %if %{with testsuite} BuildRequires: python3 %endif -%if %{with manual} +%if %{with docs} # for /usr/bin/sphinx-build BuildRequires: python2-sphinx %endif @@ -96,12 +96,12 @@ BuildRequires: autoconf BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} -%if %{with haddock} +%if %{with docs} Requires: ghc-doc-cron = %{version}-%{release} %endif Requires: ghc-ghc-devel = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} -%if %{with manual} +%if %{with docs} Requires: ghc-manual = %{version}-%{release} %endif @@ -138,7 +138,7 @@ Requires(post): chkconfig Requires(postun): chkconfig # added in f14 Obsoletes: ghc-doc < 6.12.3-4 -%if %{without haddock} +%if %{without docs} Obsoletes: ghc-doc-cron < %{version}-%{release} # added in f28 Obsoletes: ghc-doc-index < %{version}-%{release} @@ -155,7 +155,7 @@ To install all of ghc (including the ghc library), install the main ghc package. -%if %{with haddock} +%if %{with docs} %package doc-cron Summary: GHC library documentation indexing cronjob License: BSD @@ -171,7 +171,7 @@ documention. %endif -%if %{with manual} +%if %{with docs} %package manual Summary: GHC manual License: BSD @@ -226,7 +226,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD time-1.8.0.2 %ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 -%if %{with haddock} +%if %{with docs} %ghc_lib_subpackage -d -l BSD xhtml-3000.2.2 %endif %endif @@ -273,7 +273,7 @@ rm -r libffi-tarballs %patch28 -p1 -b .orig %global gen_contents_index gen_contents_index.orig -%if %{with haddock} +%if %{with docs} if [ ! -f "libraries/%{gen_contents_index}" ]; then echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!" exit 1 @@ -299,15 +299,14 @@ BuildFlavour = quick %endif %endif GhcLibWays = v dyn %{?with_prof:p} -%if %{without haddock} -HADDOCK_DOCS = NO -%endif -EXTRA_HADDOCK_OPTS += --hyperlinked-source -%if %{with manual} +%if %{with docs} +HADDOCK_DOCS = yes BUILD_MAN = yes %else +HADDOCK_DOCS = no BUILD_MAN = no %endif +EXTRA_HADDOCK_OPTS += --hyperlinked-source BUILD_SPHINX_PDF=no EOF ## for verbose build output @@ -430,7 +429,7 @@ done %ghc_strip_dynlinked -%if %{with haddock} +%if %{with docs} mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index mkdir -p %{buildroot}%{_localstatedir}/lib/ghc @@ -569,14 +568,14 @@ fi %{ghclibdir}/template-hsc.h %dir %{_docdir}/ghc %dir %{ghc_html_dir} -%if %{with haddock} +%if %{with docs} %{_bindir}/ghc-doc-index %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} %{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex -%if %{with manual} +%if %{with docs} # https://ghc.haskell.org/trac/ghc/ticket/12939 #%%{_mandir}/man1/ghc.* %endif @@ -596,7 +595,7 @@ fi %ghost %{_localstatedir}/lib/ghc/pkg-dir.cache.new %endif -%if %{with haddock} +%if %{with docs} %files doc-cron %config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index %endif @@ -604,11 +603,13 @@ fi %files libraries -%if %{with manual} +%if %{with docs} %files manual ## needs pandoc #%%{ghc_html_dir}/Cabal +%if %{with docs} %{ghc_html_dir}/haddock +%endif %{ghc_html_dir}/index.html %{ghc_html_dir}/users_guide %endif From 7a2103797fa6b3ad6f283f4269212ba9457e35c0 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 29 May 2018 00:03:28 +0900 Subject: [PATCH 462/530] add changelogs for docs build changes --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index b77c1f5..3e749dd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -23,7 +23,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 67%{?dist} +Release: 68%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -616,7 +616,11 @@ fi %changelog -* Thu May 24 2018 Jens Petersen - 8.2.2-67 +* Mon May 28 2018 Jens Petersen - 8.2.2-68 +- fix sphinx-build version detection +- merge bcond for haddock and manual + +* Mon May 28 2018 Jens Petersen - 8.2.2-67 - move manuals to ghc-manual.noarch - rename ghc-doc-index to ghc-doc-cron.noarch - ghost the ghc-doc-index local state files From 23c7272d25d6b359c1a88bcfb4604bec8cace879 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 30 May 2018 16:45:25 +0900 Subject: [PATCH 463/530] add ghc_llvm_archs --- ghc.spec | 16 +++++++++------- 1 file changed, 9 insertions(+), 7 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3e749dd..36ba5fe 100644 --- a/ghc.spec +++ b/ghc.spec @@ -16,6 +16,11 @@ # to handle RCs %global ghc_release %{version} +# 8.2 needs llvm-3.9 +%global llvm_major 3.9 + +%global ghc_llvm_archs armv7hl aarch64 + Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems Version: 8.2.2 @@ -53,9 +58,6 @@ Patch26: ghc-Debian-no-missing-haddock-file-warning.patch Patch27: ghc-Debian-reproducible-tmp-names.patch Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch -# 8.2 needs llvm-3.9 -%global llvm_major 3.9 - # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel @@ -86,7 +88,7 @@ BuildRequires: python3 # for /usr/bin/sphinx-build BuildRequires: python2-sphinx %endif -%ifarch armv7hl aarch64 +%ifarch %{ghc_llvm_archs} BuildRequires: llvm%{llvm_major} %endif # patch5 @@ -143,7 +145,7 @@ Obsoletes: ghc-doc-cron < %{version}-%{release} # added in f28 Obsoletes: ghc-doc-index < %{version}-%{release} %endif -%ifarch armv7hl aarch64 +%ifarch %{ghc_llvm_archs} Requires: llvm%{llvm_major} %endif @@ -286,13 +288,13 @@ fi # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF %if %{with perf_build} -%ifarch armv7hl aarch64 +%ifarch %{ghc_llvm_archs} BuildFlavour = perf-llvm %else BuildFlavour = perf %endif %else -%ifarch armv7hl aarch64 +%ifarch %{ghc_llvm_archs} BuildFlavour = quick-llvm %else BuildFlavour = quick From e47b032afdfd7a54e39ace31a623d3a1cb230c27 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 1 Jun 2018 16:05:10 +0900 Subject: [PATCH 464/530] disable testsuite, bootstrap and build fixes --- ghc.spec | 52 +++++++++++++++++++++++++++++----------------------- 1 file changed, 29 insertions(+), 23 deletions(-) diff --git a/ghc.spec b/ghc.spec index 36ba5fe..3c88211 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,11 +1,14 @@ # perf production build (disable for quick build) %bcond_without perf_build +# to handle RCs +%global ghc_release %{version} + # make sure ghc libraries' ABI hashes unchanged %bcond_without abicheck -# run testsuite -%bcond_without testsuite +# run testsuite (takes time and not really being using) +%bcond_with testsuite # build profiling libraries %bcond_without prof # build docs (haddock and manuals) @@ -13,12 +16,8 @@ # %bcond_without docs -# to handle RCs -%global ghc_release %{version} - # 8.2 needs llvm-3.9 %global llvm_major 3.9 - %global ghc_llvm_archs armv7hl aarch64 Name: ghc @@ -63,10 +62,10 @@ Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch # and retired arches: alpha sparcv9 armv5tel # see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -%if %{with abicheck} -BuildRequires: ghc-compiler = %{version} +BuildRequires: ghc-compiler # for ABI hash checking -BuildRequires: ghc = %{version} +%if %{with abicheck} +BuildRequires: ghc %endif BuildRequires: ghc-rpm-macros-extra >= 1.8 BuildRequires: ghc-binary-devel @@ -86,7 +85,7 @@ BuildRequires: python3 %endif %if %{with docs} # for /usr/bin/sphinx-build -BuildRequires: python2-sphinx +BuildRequires: python-sphinx %endif %ifarch %{ghc_llvm_archs} BuildRequires: llvm%{llvm_major} @@ -302,7 +301,7 @@ BuildFlavour = quick %endif GhcLibWays = v dyn %{?with_prof:p} %if %{with docs} -HADDOCK_DOCS = yes +#HADDOCK_DOCS = yes BUILD_MAN = yes %else HADDOCK_DOCS = no @@ -360,14 +359,15 @@ make %{?_smp_mflags} %install make DESTDIR=%{buildroot} install +%if %{defined _ghcdynlibdir} mv %{buildroot}%{ghclibdir}/*/libHS*ghc%{ghc_version}.so %{buildroot}%{_libdir}/ for i in $(find %{buildroot} -type f -exec sh -c "file {} | grep -q 'dynamically linked'" \; -print); do chrpath -d $i done - for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_libdir}!' $i done +%endif for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") @@ -380,8 +380,7 @@ echo "%%license libraries/$name/LICENSE" >> ghc-$name.files %endif done -# ghc-base should own ghclibdir -echo "%%dir %{ghclibdir}" >> ghc-base-devel.files +echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} @@ -403,21 +402,26 @@ echo "%%license libraries/LICENSE.%1" >> ghc-%2.files\ %merge_filelist ghc-prim base # add rts libs +%if %{defined _ghcdynlibdir} echo "%{ghclibdir}/rts" >> ghc-base-devel.files -ls %{buildroot}%{_libdir}/libHSrts*.so >> ghc-base.files +%else +echo "%%dir %{ghclibdir}/rts" >> ghc-base.files +ls -d %{buildroot}%{ghclibdir}/rts/lib*.a >> ghc-base-devel.files +%endif +ls %{buildroot}%{?_ghcdynlibdir}%{!?_ghcdynlibdir:%{ghclibdir}/rts}/libHSrts*.so >> ghc-base.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files %endif +%if %{defined _ghcdynlibdir} sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf - -sed -i -e "s|^%{buildroot}||g" ghc-base.files +%endif ls -d %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files %if 0%{?rhel} && 0%{?rhel} < 7 ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files %endif -sed -i -e "s|^%{buildroot}||g" ghc-base-devel.files +sed -i -e "s|^%{buildroot}||g" ghc-base*.files # these are handled as alternatives for i in hsc2hs runhaskell; do @@ -493,6 +497,8 @@ if [ "%{version}" = "$(ghc --numeric-version)" ]; then echo "ghc ABI hash change: aborting build!" >&2 exit 1 fi +else + echo "ABI hash checks skipped: GHC changed from $(ghc --numeric-version) to %{version}" fi %endif @@ -579,7 +585,7 @@ fi %{ghclibdir}/latex %if %{with docs} # https://ghc.haskell.org/trac/ghc/ticket/12939 -#%%{_mandir}/man1/ghc.* +#%%{_mandir}/man1/ghc.1* %endif %dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index @@ -609,9 +615,7 @@ fi %files manual ## needs pandoc #%%{ghc_html_dir}/Cabal -%if %{with docs} %{ghc_html_dir}/haddock -%endif %{ghc_html_dir}/index.html %{ghc_html_dir}/users_guide %endif @@ -621,10 +625,12 @@ fi * Mon May 28 2018 Jens Petersen - 8.2.2-68 - fix sphinx-build version detection - merge bcond for haddock and manual +- disable the testsuite to speed up builds +- version bootstrap and packaging fixes and tweaks * Mon May 28 2018 Jens Petersen - 8.2.2-67 -- move manuals to ghc-manual.noarch -- rename ghc-doc-index to ghc-doc-cron.noarch +- move manuals to new ghc-manual (noarch) +- rename ghc-doc-index to ghc-doc-cron (noarch) - ghost the ghc-doc-index local state files - ghost some newer libraries index files - simplify and extend bcond for build configuration From c3c344a19d8eea4b1d0d5cee9d2086ca22d33afe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 1 Jul 2018 20:39:51 +0900 Subject: [PATCH 465/530] use uppercase YES and NO in build.mk lowercase is not supported --- ghc.spec | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3c88211..e3658d8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -301,14 +301,14 @@ BuildFlavour = quick %endif GhcLibWays = v dyn %{?with_prof:p} %if %{with docs} -#HADDOCK_DOCS = yes -BUILD_MAN = yes +HADDOCK_DOCS = YES +BUILD_MAN = YES %else -HADDOCK_DOCS = no -BUILD_MAN = no +HADDOCK_DOCS = NO +BUILD_MAN = NO %endif EXTRA_HADDOCK_OPTS += --hyperlinked-source -BUILD_SPHINX_PDF=no +BUILD_SPHINX_PDF = NO EOF ## for verbose build output #GhcStage1HcOpts=-v4 From efa1bb8c54326b5d0da46a58dbf5153059113320 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 8 Jul 2018 07:50:26 +0200 Subject: [PATCH 466/530] add manpages from Debian --- ghc-pkg.man | 228 +++++++++++++++++++++++++++++++++++++++++++++++++++ ghc.spec | 11 +++ haddock.man | 231 ++++++++++++++++++++++++++++++++++++++++++++++++++++ runghc.man | 45 ++++++++++ 4 files changed, 515 insertions(+) create mode 100644 ghc-pkg.man create mode 100644 haddock.man create mode 100644 runghc.man diff --git a/ghc-pkg.man b/ghc-pkg.man new file mode 100644 index 0000000..ccac8e4 --- /dev/null +++ b/ghc-pkg.man @@ -0,0 +1,228 @@ +.TH ghc-pkg 1 "2010-01-27" +.SH NAME +ghc-pkg \- GHC Haskell Cabal package manager +.SH SYNOPSIS +.B ghc-pkg +.I action +.RI [ OPTION ]... +.SH DESCRIPTION +A package is a library of Haskell modules known to the compiler. The +.B ghc-pkg +tool allows adding or removing them from a package database. By +default, the system-wide package database is modified, but +alternatively the user's local package database or another specified +file can be used. +.PP +To make a package available for +.BR ghc , +.B ghc-pkg +can be used to register it. Unregistering it removes it from the +database. Also, packages can be hidden, to make +.B ghc +ignore the package by default, without uninstalling it. Exposing a +package makes a hidden package available. Additionally, +.B ghc-pkg +has various commands to query the package database. +.PP +Where a package name is required, the package can be named in full +including the version number (e.g. +.BR network-1.0 ), +or without the version number. Naming a package without the version +number matches all versions of the package; the specified action will +be applied to all the matching packages. A package specifier that +matches all version of the package can also be written +.BR pkg-* , +to make it clearer that multiple packages are being matched. +.SH ACTIONS +.TP +\fBregister\fP \fIfilename\fP|\fB-\fP +Register the package using the specified installed package +description. +.TP +\fBupdate\fP \fIfilename\fP|\fB-\fP +Register the package, overwriting any other package with the same +name. +.TP +\fBunregister\fP \fIpkg-id\fP +Unregister the specified package. +.TP +\fBexpose\fP \fIpkg-id\fP +Expose the specified package. +.TP +\fBhide\fP \fIpkg-id\fP +Hide the specified package +.TP +\fBlist\fP \fR[\fIpkg\fR]...\fP +List registered packages in the global database, and also the user +database if +.B --user +is given. If a package name is given all the registered versions will +be listed in ascending order. Accepts the +.B --simple-output +flag. +.TP +.B dot +Generate a graph of the package dependencies in a form suitable for +input for the graphviz tools. For example, to generate a PDF of the +dependency graph: +.br +\fB dot \| tred \| dot -Tpdf >pkgs.pdf\fP +.TP +\fBfind-module\fP \fImodule\fP +List registered packages exposing module +.I module +in the global database, and also the user database if +.B --user +is given. All the registered versions will be listed in ascending +order. Accepts the +.B --simple-output +flag. +.TP +\fBlatest\fP \fIpkg-id\fP +Prints the highest registered version of a package. +.TP +.B check +Check the consistency of package dependencies and list broken +packages. Accepts the +.B --simple-output +flag. +.TP +\fBdescribe\fP \fIpkg\fP +Give the registered description for the +specified package. The description is returned in precisely the syntax +required by ghc-pkg register. +.TP +\fBfield\fP \fIpkg field\fP +Extract the specified field of the package description for the +specified package. Accepts comma-separated multiple fields. +.TP +.B dump +Dump the registered description for every package. This is like +.BR ghc-pkg\ describe\ '*' , +expect that it is intended to be used by tools that parse the results, +rather than humans. +.TP +.B recache +Regenerate the package database cache. This command should only be +necessary if you added a package to the database by dropping a file +into the database directory manyally. By default, the global DB is +recached; to recache a different DB use +.B --user +or +.B --package-conf +as appropriate. +.SH OPTIONS +When asked to modify a database +.RB ( register ,\ unregister ,\ update ,\ hide ,\ expose ,\ and\ also\ check ), +.B ghc-pkg +modifies the global database by +default. Specifying +.B --user +causes it to act on the user database, +or +.B --package-conf +can be used to act on another database +entirely. When multiple of these options are given, the rightmost +one is used as the database to act upon. +.PP +Commands that query the package database +.RB ( list ,\ latest ,\ describe ,\ field ) +operate on the list of databases specified by the flags +.BR --user ,\ --global , +and +.BR --package-conf . +If none of these flags are +given, the default is +.BR --global\ --user . +.TP +.B --user +Use the current user's package database. +.TP +.B --global +Use the global package database. +.TP +\fB-f\fP \fIFILE\fP, \fB--package-conf=\fIFILE\fP +Use the specified package config file. +.TP +.BI --global-conf= FILE +Location of the global package config. +.TP +.B --force +Ignore missing dependencies, directories, and libraries. +.TP +.B --force-files +Ignore missing directories and libraries only. +.TP +.BR -g ,\ --auto-ghc-libs +Automatically build libs for GHCi (with register). +.TP +.BR -? ,\ --help +Display a help message and exit. +.TP +.BR -V ,\ --version +Output version information and exit. +.TP +.B --simple-output +Print output in easy-to-parse format for some commands. +.TP +.B --names-only +Only print package names, not versions; can only be used with +.BR list\ --simple-output . +.TP +.B --ignore-case +Ignore case for substring matching. +.SH ENVIRONMENT VARIABLES +.TP +.B GHC_PACKAGE_PATH +The +.B GHC_PACKAGE_PATH +environment variable may be set to a +.BR : -separated +list of files containing package databases. This list of package +databases is used by +.B ghc +and +.BR ghc-pkg , +with earlier databases in the list overriding later ones. This order +was chosen to match the behaviour of the +.B PATH +environment variable; think of it as a list of package databases that +are searched left-to-right for packages. + +If +.B GHC_PACKAGE_PATH +ends in a separator, then the default user and system package +databases are appended, in that order. e.g. to augment the usual set +of packages with a database of your own, you could say: + +.br +\fB export GHC_PACKAGE_PATH=$HOME/.my-ghc-packages.conf:\fP +.br + +To check whether your +.B GHC_PACKAGE_PATH +setting is doing the right thing, +.B ghc-pkg list +will list all the databases in use, in the reverse order they are +searched. +.SH FILES +Both of these locations are changed for Debian. Upstream still keeps +these under +.IR /usr . +Some programs may refer to that, but look in +.I /var +instead. +.TP +.I /var/lib/ghc/package.conf +Global package.conf file. +.TP +.I /var/lib/ghc/package.conf.d/ +Directory for library specific package.conf files. These are added to +the global registry. +.SH "SEE ALSO" +.BR ghc (1), +.BR runghc (1), +.BR hugs (1). +.SH AUTHOR +This manual page was written by Kari Pahula , for the +Debian project (and may be used by others). diff --git a/ghc.spec b/ghc.spec index e3658d8..24cc6d6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -38,6 +38,9 @@ Source1: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-testsu %endif Source3: ghc-doc-index.cron Source4: ghc-doc-index +Source5: ghc-pkg.man +Source6: haddock.man +Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch @@ -451,6 +454,10 @@ cd .. # we package the library license files separately find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';' +mkdir -p %{buildroot}%{_mandir}/man1 +install -p -m 0644 %{SOURCE5} %{buildroot}%{_mandir}/man1/ghc-pkg.1 +install -p -m 0644 %{SOURCE6} %{buildroot}%{_mandir}/man1/haddock.1 +install -p -m 0644 %{SOURCE7} %{buildroot}%{_mandir}/man1/runghc.1 %check export LANG=en_US.utf8 @@ -576,6 +583,10 @@ fi %{ghclibdir}/template-hsc.h %dir %{_docdir}/ghc %dir %{ghc_html_dir} +%{_mandir}/man1/ghc-pkg.1* +%{_mandir}/man1/haddock.1* +%{_mandir}/man1/runghc.1* + %if %{with docs} %{_bindir}/ghc-doc-index %{_bindir}/haddock diff --git a/haddock.man b/haddock.man new file mode 100644 index 0000000..a30106b --- /dev/null +++ b/haddock.man @@ -0,0 +1,231 @@ +.TH HADDOCK 1 "July 2010" "Haddock, version 2.6.1" "Haddock documentation generator" + + +.SH NAME +haddock \- documentation tool for annotated Haskell source code + + +.SH SYNOPSIS +.B haddock +.RI [ options ] " file" ... + + +.SH DESCRIPTION +This manual page documents briefly the +.B haddock +command. +Extensive documentation is available in various other formats including DVI, +PostScript and HTML; see below. + +.PP +.I file +is a filename containing a Haskell source module. +All the modules specified on the command line will be processed together. +When one module refers to an entity in another module being processed, the +documentation will link directly to that entity. + +Entities that cannot be found, for example because they are in a module that +is not being processed as part of the current batch, simply will not be +hyperlinked in the generated documentation. +.B haddock +will emit warnings listing all the identifiers it could not resolve. + +The modules should not be mutually recursive, as +.B haddock +does not like swimming in circles. + + +.SH OPTIONS +The programs follow the usual GNU command line syntax, with long +options starting with two dashes (`--'). +A summary of options is included below. +For a complete description, see the other documentation. + +.TP +\fB\-o \fIDIR\fP, \-\-odir=\fIDIR\fP +directory in which to put the output files + +.TP +\fB\-i \fIFILE\fP, \-\-read-interface=\fIFILE\fP +read an interface from +.IR FILE . + +.TP +\fB\-D \fIFILE\fP, \-\-dump\-interface=\fIFILE\fP +dump an interface for these modules in +.IR FILE . + +.TP +\fB\-l \fIDIR\fP, \-\-lib=\fIDIR\fP +location of Haddock's auxiliary files + +.TP +.BR \-h ", " \-\-html +Generate documentation in HTML format. +Several files will be generated into the current directory (or the specified +directory if the +.B \-o +option is given), including the following: +.RS +.TP +.I index.html +The top level page of the documentation: +lists the modules available, using indentation to represent the hierarchy if +the modules are hierarchical. +.TP +.I haddock.css +The stylesheet used by the generated HTML. +Feel free to modify this to change the colors or layout, or even specify +your own stylesheet using the +.B \-\-css +option. +.TP +.I module.html +An HTML page for each module. +.TP +.IR doc-index.html ", " doc-index-XX.html +The index, split into two (functions/constructors and types/classes, as per +Haskell namespaces) and further split alphabetically. +.RE + +.TP +.B \-\-hoogle +output for Hoogle + +.TP +\fB\-\-html\-help=\fIformat +produce index and table of contents in mshelp, mshelp2 or devhelp format +(with \fI\-h\fP) + +.TP +\fB\-\-source\-base=\fPURL +Include links to the source files in the generated documentation, where URL +is the base URL where the source files can be found. + +.TP +\fB\-s \fPURL, \fB\-\-source\-module=\fPURL +Include links to the source files in the generated documentation, where URL +is a source code link for each module (using the %{FILE} or %{MODULE} vars). + +.TP +\fB\-\-source\-entity=\fPURL +Include links to the source files in the generated documentation, where URL +is a source code link for each entity (using the %{FILE}, %{MODULE} or %{NAME} vars). + +.TP +\fB\-\-comments\-base=\fPURL +URL for a comments link on the contents and index pages. +.TP +\fB\-\-comments\-module=\fPURL +URL for a comments link for each module (using the %{MODULE} var). +.TP +\fB\-\-comments\-entity=\fPURL +URL for a comments link for each entity (using the %{FILE}, %{MODULE} or %{NAME} vars). +.TP +.BI \-\-css= FILE +Use the CSS +.I FILE +instead of the default stylesheet that comes with +.B haddock +for HTML output. It should specify certain classes: see the default stylesheet for details. + +.TP +\fB\-p \fIFILE\fP, \-\-prologue=\fIFILE\fP +Specify a file containing prologue text. + +.TP +\fB\-t \fITITLE\fP, \-\-title=\fITITLE\fP +Use \fITITLE\fP as the page heading for each page in the documentation. +This will normally be the name of the library being documented. + +The title should be a plain string (no markup please!). + +.TP +\fB\-k \fINAME\fP, \-\-package=\fINAME\fP +Specify the package name (optional). + +.TP +.BR \-n ", " \-\-no\-implicit\-prelude +do not assume Prelude is imported + +.TP +.BR \-d ", " \-\-debug +Enable extra debugging output. + +.TP +.BR \-? ", " \-\-help +Display help. + +.TP +.BR \-V ", " \-\-version +Display version. + +.TP +.BR \-v ", " \-\-verbose +Verbose status reporting. + +.TP +\fB\-\-use\-contents=\fPURL +Use a separately-generated HTML contents page. + +.TP +.B \-\-gen\-contents +Generate an HTML contents from specified interfaces. + +.TP +\fB\-\-use\-index=\fPURL +Use a separately-generated HTML index. + +.TP +.B \-\-gen\-index +Generate an HTML index from specified interfaces. + +.TP +.B \-\-ignore\-all\-exports +Behave as if all modules have the ignore-exports atribute + +.TP +\fB\-\-hide=\fIMODULE +Behave as if \fIMODULE\fP has the hide attribute. + +.TP +\fB\-\-use\-package=\fIPACKAGE +The modules being processed depend on \fIPACKAGE\fP. + +.SH FILES +.I /usr/bin/haddock +.br +.I /usr/share/haddock-2.6.1/html/plus.gif +.br +.I /usr/share/haddock-2.6.1/html/minus.gif +.br +.I /usr/share/haddock-2.6.1/html/haskell_icon.gif +.br +.I /usr/share/haddock-2.6.1/html/haddock.js +.br +.I /usr/share/haddock-2.6.1/html/haddock.css +.br +.I /usr/share/haddock-2.6.1/html/haddock-DEBUG.css + +.SH SEE ALSO +.IR /usr/share/doc/haddock/ , +.br +the Haddock homepage +.UR http://haskell.org/haddock/ +(http://haskell.org/haddock/) +.UE + +.SH COPYRIGHT +Haddock version 2.6.1 + +Copyright 2006-2010 Simon Marlow , Dawid Waern . +All rights reserved. + + +.SH AUTHOR +This manual page was written by Michael Weber +for the Debian GNU/Linux system (but may be used by others). + +.\" Local variables: +.\" mode: nroff +.\" End: diff --git a/runghc.man b/runghc.man new file mode 100644 index 0000000..61a9076 --- /dev/null +++ b/runghc.man @@ -0,0 +1,45 @@ +.TH RUNGHC 1 "28 NOVEMBER 2007" +.SH NAME +runghc \- program to run Haskell programs without first having to compile them. +.SH SYNOPSIS +.B runghc +.RI +[runghc|flags] [GHC|flags] module [program|flags]... +.br +.SH DESCRIPTION +.B runghc +is considered a non-interactive interpreter and part of The Glasgow Haskell Compiler. +.B runghc +is a compiler that automatically runs its results at the end. +.PP +.SH OPTIONS +.TP +the flags are: +.TP +.B \-f +it tells runghc which GHC to use to run the program. If it is not given then runghc will search for GHC in the directories in the system search path. runghc -f /path/to/ghc +.TP +.B \-- +runghc will try to work out where the boundaries between [runghc flags] and [GHC flags], and [GHC flags] and module are, but you can use a -- flag if it doesn't get it right. For example, runghc -- -fglasgow-exts Foo +means runghc won't try to use glasgow-exts as the path to GHC, but instead will pass the flag to GHC. + +.SH EXAMPLES +.TP +.B runghc foo +.PP +.B runghc -f /path/to/ghc foo +.TP +.B runghc -- -fglasgow-exts Foo + +.SH SEE ALSO +.BR ghc (1), +.BR ghci (1). +.br + +.SH COPYRIGHT +Copyright 2002, The University Court of the University of Glasgow. All rights reserved. + +.SH AUTHOR +This manual page was written by Efrain Valles Pulgar . This is free documentation; see the GNU +General Public Licence version 2 or later for copying conditions. There is NO WARRANTY. + From fab792e3e2073a5ea5a8b88756add50e5088cfdf Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 8 Jul 2018 07:50:52 +0200 Subject: [PATCH 467/530] improve testsuite comment --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 24cc6d6..6b2c2df 100644 --- a/ghc.spec +++ b/ghc.spec @@ -7,7 +7,7 @@ # make sure ghc libraries' ABI hashes unchanged %bcond_without abicheck -# run testsuite (takes time and not really being using) +# skip testsuite (takes time and not really being used) %bcond_with testsuite # build profiling libraries %bcond_without prof From 485e042556f0222f59f41bab497283c58824f0ca Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 9 Jul 2018 12:29:54 +0200 Subject: [PATCH 468/530] ghc manpage is now built --- ghc.spec | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6b2c2df..8265a2f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -595,8 +595,7 @@ fi %{ghclibdir}/html %{ghclibdir}/latex %if %{with docs} -# https://ghc.haskell.org/trac/ghc/ticket/12939 -#%%{_mandir}/man1/ghc.1* +%{_mandir}/man1/ghc.1* %endif %dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index From 8de86546c3b2ca2041a2f1e24ebb5826769acd14 Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Fri, 13 Jul 2018 01:28:32 +0000 Subject: [PATCH 469/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_29_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 8265a2f..77dd986 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 68%{?dist} +Release: 69%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -632,6 +632,9 @@ fi %changelog +* Fri Jul 13 2018 Fedora Release Engineering - 8.2.2-69 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_29_Mass_Rebuild + * Mon May 28 2018 Jens Petersen - 8.2.2-68 - fix sphinx-build version detection - merge bcond for haddock and manual From 01d69666550e88f70c18f00c41dc2d3a227b849b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 24 Jul 2018 19:13:19 +0900 Subject: [PATCH 470/530] (aarch64/s390) remove -Wall and -Werror=format-security separately --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 77dd986..686b95b 100644 --- a/ghc.spec +++ b/ghc.spec @@ -332,7 +332,7 @@ autoconf %else # -Wunused-label is extremely noisy %ifarch aarch64 s390x -CFLAGS="${CFLAGS:-$(echo %optflags | sed -e 's/-Wall -Werror=format-security //')}" +CFLAGS="${CFLAGS:-$(echo %optflags | sed -e 's/-Wall //' -e 's/-Werror=format-security //')}" %else CFLAGS="${CFLAGS:-%optflags}" %endif From db7639c4b736427ed6f0e91dec5744f319501dec Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Miro=20Hron=C4=8Dok?= Date: Mon, 6 Aug 2018 21:36:53 +0200 Subject: [PATCH 471/530] Use python3-sphinx to build the docs --- ghc.spec | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 686b95b..3914fb6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -87,8 +87,7 @@ BuildRequires: perl-interpreter BuildRequires: python3 %endif %if %{with docs} -# for /usr/bin/sphinx-build -BuildRequires: python-sphinx +BuildRequires: python3-sphinx %endif %ifarch %{ghc_llvm_archs} BuildRequires: llvm%{llvm_major} From 7e4456e936302e2b2738c6fc9ea2c50e8e407c9e Mon Sep 17 00:00:00 2001 From: Peter Robinson Date: Tue, 16 Oct 2018 12:33:21 +0100 Subject: [PATCH 472/530] Update alternatives dependencies --- ghc.spec | 9 ++++++--- 1 file changed, 6 insertions(+), 3 deletions(-) diff --git a/ghc.spec b/ghc.spec index 3914fb6..52dab2c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -27,7 +27,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 69%{?dist} +Release: 70%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -137,8 +137,8 @@ License: BSD Requires: gcc%{?_isa} Requires: ghc-base-devel%{?_isa} # for alternatives -Requires(post): chkconfig -Requires(postun): chkconfig +Requires(post): %{_sbindir}/update-alternatives +Requires(postun): %{_sbindir}/update-alternatives # added in f14 Obsoletes: ghc-doc < 6.12.3-4 %if %{without docs} @@ -631,6 +631,9 @@ fi %changelog +* Tue Oct 16 2018 Peter Robinson 8.2.2-70 +- Update alternatives dependencies + * Fri Jul 13 2018 Fedora Release Engineering - 8.2.2-69 - Rebuilt for https://fedoraproject.org/wiki/Fedora_29_Mass_Rebuild From 76212895efb6bcab51974778db9012fc6d159c84 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Oct 2018 12:07:29 +0900 Subject: [PATCH 473/530] backport build configs from 8.4 module; extend quickbuild to perf_build - backport quickbuild config from 8.4 module - disable -Wall on s390x like in 8.4 module to silence warning flood and simplify setting of CFLAGS - setup build.mk in setup section, taken from copr and module - enable buildpath-abi-stability.patch (from Debian) --- ghc-Debian-buildpath-abi-stability.patch | 14 +++--- ghc.spec | 63 +++++++++++++++--------- 2 files changed, 46 insertions(+), 31 deletions(-) diff --git a/ghc-Debian-buildpath-abi-stability.patch b/ghc-Debian-buildpath-abi-stability.patch index b6f46b6..1d45c72 100644 --- a/ghc-Debian-buildpath-abi-stability.patch +++ b/ghc-Debian-buildpath-abi-stability.patch @@ -1,10 +1,8 @@ Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 -Index: ghc-7.10.1/compiler/iface/MkIface.hs -=================================================================== ---- ghc-7.10.1.orig/compiler/iface/MkIface.hs 2015-05-17 20:34:02.808643844 +0200 -+++ ghc-7.10.1/compiler/iface/MkIface.hs 2015-05-17 20:34:02.804643799 +0200 -@@ -611,7 +611,7 @@ +--- a/compiler/iface/MkIface.hs ++++ b/compiler/iface/MkIface.hs +@@ -681,7 +681,7 @@ addFingerprints hsc_env mb_old_fingerpri iface_hash <- computeFingerprint putNameLiterally (mod_hash, ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache @@ -13,7 +11,7 @@ Index: ghc-7.10.1/compiler/iface/MkIface.hs sorted_deps, mi_hpc iface0) -@@ -644,6 +644,9 @@ +@@ -714,6 +714,9 @@ addFingerprints hsc_env mb_old_fingerpri (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) fix_fn = mi_fix_fn iface0 ann_fn = mkIfaceAnnCache (mi_anns iface0) @@ -21,5 +19,5 @@ Index: ghc-7.10.1/compiler/iface/MkIface.hs + usages = [ case u of UsageFile _ fp -> UsageFile "" fp; _ -> u | u <- mi_usages iface0 ] + - getOrphanHashes :: HscEnv -> [Module] -> IO [Fingerprint] - getOrphanHashes hsc_env mods = do + -- | Retrieve the orphan hashes 'mi_orphan_hash' for a list of modules + -- (in particular, the orphan modules which are transitively imported by the diff --git a/ghc.spec b/ghc.spec index 52dab2c..b1236e6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,6 @@ -# perf production build (disable for quick build) -%bcond_without perf_build +# disable prof, docs, perf build +# NB This SHOULD be disabled 'bcond_with' for all koji production builds +%bcond_with quickbuild # to handle RCs %global ghc_release %{version} @@ -9,12 +10,22 @@ # skip testsuite (takes time and not really being used) %bcond_with testsuite + # build profiling libraries -%bcond_without prof # build docs (haddock and manuals) -# combined since disabling haddock seems to cause no manuals built -# +# - combined since disabling haddock seems to cause no manuals built +# - +# perf production build (disable for quick build) +%if %{with quickbuild} +%bcond_with prof +%bcond_with docs +%bcond_with perf_build +%else +%bcond_without prof %bcond_without docs +%bcond_without perf_build +%endif + # 8.2 needs llvm-3.9 %global llvm_major 3.9 @@ -53,9 +64,12 @@ Patch5: ghc-configure-fix-sphinx-version-check.patch Patch12: ghc-armv7-VFPv3D16--NEON.patch +# for s390x +# https://ghc.haskell.org/trac/ghc/ticket/15689 +Patch15: ghc-warnings.mk-CC-Wall.patch + # Debian patches: -# doesn't apply to 8.2 -#Patch24: ghc-Debian-buildpath-abi-stability.patch +Patch24: ghc-Debian-buildpath-abi-stability.patch Patch26: ghc-Debian-no-missing-haddock-file-warning.patch Patch27: ghc-Debian-reproducible-tmp-names.patch Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch @@ -270,7 +284,11 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif -#%%patch24 -p1 -b .orig +%ifarch s390x +%patch15 -p1 -b .orig +%endif + +%patch24 -p1 -b .orig %patch26 -p1 -b .orig %patch27 -p1 -b .orig %patch28 -p1 -b .orig @@ -283,8 +301,6 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then fi %endif - -%build # http://hackage.haskell.org/trac/ghc/wiki/Platforms # cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc cat > mk/build.mk << EOF @@ -318,6 +334,7 @@ EOF ## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) #EXTRA_HC_OPTS=-debug +%build # for patch12 %ifarch armv7hl autoreconf @@ -326,19 +343,10 @@ autoreconf autoconf %endif -%if 0%{?fedora} > 28 -%ghc_set_cflags -%else -# -Wunused-label is extremely noisy -%ifarch aarch64 s390x -CFLAGS="${CFLAGS:-$(echo %optflags | sed -e 's/-Wall //' -e 's/-Werror=format-security //')}" -%else -CFLAGS="${CFLAGS:-%optflags}" -%endif -export CFLAGS -%endif +# replace later with ghc_set_gcc_flags +export CFLAGS="${CFLAGS:-%optflags}" export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" -# for ghc-8.2 +# for ghc >= 8.2 export CC=%{_bindir}/gcc # * %%configure induces cross-build due to different target/host/build platform names ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ @@ -624,14 +632,23 @@ fi %files manual ## needs pandoc #%%{ghc_html_dir}/Cabal +%if %{with docs} %{ghc_html_dir}/haddock +%endif %{ghc_html_dir}/index.html %{ghc_html_dir}/users_guide %endif %changelog -* Tue Oct 16 2018 Peter Robinson 8.2.2-70 +* Wed Oct 17 2018 Jens Petersen - 8.2.2-70 +- backport quickbuild config from 8.4 module and extend to perf_build +- disable -Wall on s390x like in 8.4 module to silence warning flood + and simplify setting of CFLAGS +- enable buildpath-abi-stability.patch (from Debian) +- setup build.mk in setup section, taken from copr and module + +* Tue Oct 16 2018 Peter Robinson - Update alternatives dependencies * Fri Jul 13 2018 Fedora Release Engineering - 8.2.2-69 From 1a69b5e6a474eb8380c1e105ee30768a18121fb1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Oct 2018 12:33:07 +0900 Subject: [PATCH 474/530] add missing ghc-warnings.mk-CC-Wall.patch --- ghc-warnings.mk-CC-Wall.patch | 12 ++++++++++++ 1 file changed, 12 insertions(+) create mode 100644 ghc-warnings.mk-CC-Wall.patch diff --git a/ghc-warnings.mk-CC-Wall.patch b/ghc-warnings.mk-CC-Wall.patch new file mode 100644 index 0000000..f775eb3 --- /dev/null +++ b/ghc-warnings.mk-CC-Wall.patch @@ -0,0 +1,12 @@ +--- ghc-8.4.3/mk/warnings.mk~ 2018-02-04 02:30:11.000000000 +0900 ++++ ghc-8.4.3/mk/warnings.mk 2018-09-29 14:33:37.607884921 +0900 +@@ -1,6 +1,6 @@ + # See Note [Order of warning flags]. +-SRC_CC_OPTS += -Wall $(WERROR) ++#SRC_CC_OPTS += -Wall $(WERROR) + SRC_HC_OPTS += -Wall + # Don't add -Werror to SRC_HC_OPTS_STAGE0 (or SRC_HC_OPTS), because otherwise + # validate may unnecessarily fail when booting with an older compiler. + # It would be better to only exclude certain warnings from becoming errors + +Diff finished. Sat Sep 29 14:35:43 2018 From 951062c868dc37089fddac9c1a019c47d46961fe Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Oct 2018 18:22:46 +0900 Subject: [PATCH 475/530] update ghc wiki Platforms url --- ghc.spec | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index b1236e6..dec017f 100644 --- a/ghc.spec +++ b/ghc.spec @@ -301,8 +301,7 @@ if [ ! -f "libraries/%{gen_contents_index}" ]; then fi %endif -# http://hackage.haskell.org/trac/ghc/wiki/Platforms -# cf https://github.com/gentoo-haskell/gentoo-haskell/tree/master/dev-lang/ghc +# http://ghc.haskell.org/trac/ghc/wiki/Platforms cat > mk/build.mk << EOF %if %{with perf_build} %ifarch %{ghc_llvm_archs} From abf8ce6abefaec2c415a26b078cc3fa5be284db9 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 22 Oct 2018 17:56:17 +0900 Subject: [PATCH 476/530] Recommends for ghc-manual and ghc-doc-cron --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index dec017f..92e3812 100644 --- a/ghc.spec +++ b/ghc.spec @@ -114,12 +114,12 @@ BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} %if %{with docs} -Requires: ghc-doc-cron = %{version}-%{release} +Recommends: ghc-doc-cron = %{version}-%{release} %endif Requires: ghc-ghc-devel = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} %if %{with docs} -Requires: ghc-manual = %{version}-%{release} +Recommends: ghc-manual = %{version}-%{release} %endif %description @@ -640,6 +640,9 @@ fi %changelog +* Mon Oct 22 2018 Jens Petersen +- Recommends for ghc-manual and ghc-doc-cron + * Wed Oct 17 2018 Jens Petersen - 8.2.2-70 - backport quickbuild config from 8.4 module and extend to perf_build - disable -Wall on s390x like in 8.4 module to silence warning flood From a4aebe1bb60611fb3d37bb8c115bbe47e047d1ab Mon Sep 17 00:00:00 2001 From: =?UTF-8?q?Zbigniew=20J=C4=99drzejewski-Szmek?= Date: Sun, 18 Nov 2018 23:52:46 +0100 Subject: [PATCH 477/530] Use C.UTF-8 locale --- ghc.spec | 8 ++++++-- 1 file changed, 6 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 92e3812..9e7a667 100644 --- a/ghc.spec +++ b/ghc.spec @@ -38,7 +38,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 70%{?dist} +Release: 71%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -361,7 +361,7 @@ export CC=%{_bindir}/gcc %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" -export LANG=en_US.utf8 +export LANG=C.utf8 make %{?_smp_mflags} @@ -640,6 +640,10 @@ fi %changelog +* Sun Nov 18 2018 Zbigniew Jędrzejewski-Szmek - 8.2.2-71 +- Use C.UTF-8 locale + See https://fedoraproject.org/wiki/Changes/Remove_glibc-langpacks-all_from_buildroot + * Mon Oct 22 2018 Jens Petersen - Recommends for ghc-manual and ghc-doc-cron From 8ab245d415060844da2a7b3db64ea1736a896951 Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Thu, 31 Jan 2019 21:03:15 +0000 Subject: [PATCH 478/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_30_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 9e7a667..a7e3e99 100644 --- a/ghc.spec +++ b/ghc.spec @@ -38,7 +38,7 @@ Version: 8.2.2 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 71%{?dist} +Release: 72%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -640,6 +640,9 @@ fi %changelog +* Thu Jan 31 2019 Fedora Release Engineering - 8.2.2-72 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_30_Mass_Rebuild + * Sun Nov 18 2018 Zbigniew Jędrzejewski-Szmek - 8.2.2-71 - Use C.UTF-8 locale See https://fedoraproject.org/wiki/Changes/Remove_glibc-langpacks-all_from_buildroot From 0bb8b242db863246933f40dda12f89032ec6edf3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 8 Feb 2019 10:29:42 +0800 Subject: [PATCH 479/530] backport tweaks from ghc:8.4 - add ghc_unregisterized_arches - Recommends zlib-devel - epel6 tweaks --- ghc.spec | 34 +++++++++++++++++++++------------- 1 file changed, 21 insertions(+), 13 deletions(-) diff --git a/ghc.spec b/ghc.spec index a7e3e99..99216be 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,15 +1,12 @@ # disable prof, docs, perf build -# NB This SHOULD be disabled 'bcond_with' for all koji production builds +# NB This SHOULD be disabled (bcond_with) for all koji production builds %bcond_with quickbuild -# to handle RCs -%global ghc_release %{version} - # make sure ghc libraries' ABI hashes unchanged %bcond_without abicheck -# skip testsuite (takes time and not really being used) -%bcond_with testsuite +# to handle RCs +%global ghc_release %{version} # build profiling libraries # build docs (haddock and manuals) @@ -26,11 +23,15 @@ %bcond_without perf_build %endif +# no longer build testsuite (takes time and not really being used) +%bcond_with testsuite # 8.2 needs llvm-3.9 %global llvm_major 3.9 %global ghc_llvm_archs armv7hl aarch64 +%global ghc_unregisterized_arches s390 s390x %{mips} + Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems Version: 8.2.2 @@ -113,14 +114,13 @@ BuildRequires: autoconf BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} -%if %{with docs} -Recommends: ghc-doc-cron = %{version}-%{release} -%endif Requires: ghc-ghc-devel = %{version}-%{release} Requires: ghc-libraries = %{version}-%{release} %if %{with docs} +Recommends: ghc-doc-cron = %{version}-%{release} Recommends: ghc-manual = %{version}-%{release} %endif +Recommends: zlib-devel %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -207,7 +207,7 @@ This package provides the User Guide and Haddock manual. # needs ghc_version_override for bootstrapping %global _use_internal_dependency_generator 0 %global __find_provides /usr/lib/rpm/rpmdeps --provides -%global __find_requires %{_rpmconfigdir}/ghc-deps.sh %{buildroot}%{ghclibdir} +%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} %endif %global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} @@ -355,6 +355,9 @@ export CC=%{_bindir}/gcc --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --docdir=%{_docdir}/ghc \ --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ +%ifarch %{ghc_unregisterized_arches} + --enable-unregisterised \ +%endif %if 0%{?fedora} || 0%{?rhel} > 6 --with-system-libffi \ %endif @@ -382,7 +385,7 @@ for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -%if 0%{?rhel} && 0%{?rhel} < 8 +%if 0%{?rhel} && 0%{?rhel} < 7 echo "%%doc libraries/$name/LICENSE" >> ghc-$name.files %else echo "%%license libraries/$name/LICENSE" >> ghc-$name.files @@ -401,7 +404,7 @@ echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files cat ghc-%1.files >> ghc-%2.files\ cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ -%if 0%{?rhel} && 0%{?rhel} < 8\ +%if 0%{?rhel} && 0%{?rhel} < 7\ echo "%%doc libraries/LICENSE.%1" >> ghc-%2.files\ %else\ echo "%%license libraries/LICENSE.%1" >> ghc-%2.files\ @@ -574,7 +577,7 @@ fi %{ghclibdir}/bin/ghc-iserv-prof %endif %{ghclibdir}/bin/runghc -%ifnarch s390 s390x %{mips} +%ifnarch %{ghc_unregisterized_arches} %{ghclibdir}/bin/ghc-split %endif %{ghclibdir}/bin/hp2ps @@ -640,6 +643,11 @@ fi %changelog +* Fri Feb 8 2019 Jens Petersen - 8.2.2-72 +- add ghc_unregisterized_arches +- Recommends zlib-devel +- epel6 tweaks + * Thu Jan 31 2019 Fedora Release Engineering - 8.2.2-72 - Rebuilt for https://fedoraproject.org/wiki/Fedora_30_Mass_Rebuild From 0079a61b9405cd1f2a3ec04bcabbd29e1f27c4c4 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 16 Feb 2019 00:25:45 +0800 Subject: [PATCH 480/530] update to 8.4 (rebase to 8.4 branch) --- .gitignore | 1 + ...1d895dda4600a85e01c72ff219474b5c7190.patch | 277 ++++++++++++++++++ D4159.patch | 70 ----- ...ity.patch => buildpath-abi-stability.patch | 0 fix-build-using-unregisterized-v8.2.patch | 51 ++++ ...-arm7_saner-linker-opt-handling-9873.patch | 78 ----- ghc-Cabal-install-PATH-warning.patch | 20 +- ghc-Debian-reproducible-tmp-names.patch | 43 --- ghc.spec | 87 +++--- ...h => no-missing-haddock-file-warning.patch | 0 sources | 3 +- ....patch => x32-use-native-x86_64-insn.patch | 0 12 files changed, 390 insertions(+), 240 deletions(-) create mode 100644 6e361d895dda4600a85e01c72ff219474b5c7190.patch delete mode 100644 D4159.patch rename ghc-Debian-buildpath-abi-stability.patch => buildpath-abi-stability.patch (100%) create mode 100644 fix-build-using-unregisterized-v8.2.patch delete mode 100644 ghc-7.8-arm7_saner-linker-opt-handling-9873.patch delete mode 100644 ghc-Debian-reproducible-tmp-names.patch rename ghc-Debian-no-missing-haddock-file-warning.patch => no-missing-haddock-file-warning.patch (100%) rename ghc-Debian-x32-use-native-x86_64-insn.patch => x32-use-native-x86_64-insn.patch (100%) diff --git a/.gitignore b/.gitignore index 8ced83f..5c04983 100644 --- a/.gitignore +++ b/.gitignore @@ -25,3 +25,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.0.2/ /ghc-8.2.2-src.tar.xz /ghc-8.2.2-testsuite.tar.xz +/ghc-8.4.4-src.tar.xz diff --git a/6e361d895dda4600a85e01c72ff219474b5c7190.patch b/6e361d895dda4600a85e01c72ff219474b5c7190.patch new file mode 100644 index 0000000..9f2e86a --- /dev/null +++ b/6e361d895dda4600a85e01c72ff219474b5c7190.patch @@ -0,0 +1,277 @@ +From 6e361d895dda4600a85e01c72ff219474b5c7190 Mon Sep 17 00:00:00 2001 +From: Kavon Farvardin +Date: Thu, 4 Oct 2018 13:44:55 -0400 +Subject: [PATCH] Multiple fixes / improvements for LLVM backend + +- Fix for #13904 -- stop "trashing" callee-saved registers, since it is + not actually doing anything useful. + +- Fix for #14251 -- fixes the calling convention for functions passing + raw SSE-register values by adding padding as needed to get the values + in the right registers. This problem cropped up when some args were + unused an dropped from the live list. + +- Fixed a typo in 'readnone' attribute + +- Added 'lower-expect' pass to level 0 LLVM optimization passes to + improve block layout in LLVM for stack checks, etc. + +Test Plan: `make test WAYS=optllvm` and `make test WAYS=llvm` + +Reviewers: bgamari, simonmar, angerman + +Reviewed By: angerman + +Subscribers: rwbarton, carter + +GHC Trac Issues: #13904, #14251 + +Differential Revision: https://phabricator.haskell.org/D5190 + +(cherry picked from commit adcb5fb47c0942671d409b940d8884daa9359ca4) +--- + compiler/llvmGen/Llvm/Types.hs | 2 +- + compiler/llvmGen/LlvmCodeGen/Base.hs | 62 ++++++++++++++++++++---- + compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 59 +++++----------------- + compiler/main/DriverPipeline.hs | 2 +- + testsuite/tests/codeGen/should_run/all.T | 4 +- + 5 files changed, 67 insertions(+), 62 deletions(-) + +diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs +index 87111499fc0..c1c51afcf0f 100644 +--- a/compiler/llvmGen/Llvm/Types.hs ++++ b/compiler/llvmGen/Llvm/Types.hs +@@ -560,7 +560,7 @@ instance Outputable LlvmFuncAttr where + ppr OptSize = text "optsize" + ppr NoReturn = text "noreturn" + ppr NoUnwind = text "nounwind" +- ppr ReadNone = text "readnon" ++ ppr ReadNone = text "readnone" + ppr ReadOnly = text "readonly" + ppr Ssp = text "ssp" + ppr SspReq = text "ssqreq" +diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs +index 6e20da48c1b..ec91bacc4c8 100644 +--- a/compiler/llvmGen/LlvmCodeGen/Base.hs ++++ b/compiler/llvmGen/LlvmCodeGen/Base.hs +@@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( + + cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, + llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, +- llvmPtrBits, tysToParams, llvmFunSection, ++ llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE, + + strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, + getGlobalPtr, generateExternDecls, +@@ -58,6 +58,8 @@ import ErrUtils + import qualified Stream + + import Control.Monad (ap) ++import Data.List (sort) ++import Data.Maybe (mapMaybe) + + -- ---------------------------------------------------------------------------- + -- * Some Data Types +@@ -147,16 +149,58 @@ llvmFunSection dflags lbl + -- | A Function's arguments + llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar] + llvmFunArgs dflags live = +- map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform)) ++ map (lmGlobalRegArg dflags) (filter isPassed allRegs) + where platform = targetPlatform dflags +- isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live ++ allRegs = activeStgRegs platform ++ paddedLive = map (\(_,r) -> r) $ padLiveArgs live ++ isLive r = r `elem` alwaysLive || r `elem` paddedLive + isPassed r = not (isSSE r) || isLive r +- isSSE (FloatReg _) = True +- isSSE (DoubleReg _) = True +- isSSE (XmmReg _) = True +- isSSE (YmmReg _) = True +- isSSE (ZmmReg _) = True +- isSSE _ = False ++ ++ ++isSSE :: GlobalReg -> Bool ++isSSE (FloatReg _) = True ++isSSE (DoubleReg _) = True ++isSSE (XmmReg _) = True ++isSSE (YmmReg _) = True ++isSSE (ZmmReg _) = True ++isSSE _ = False ++ ++sseRegNum :: GlobalReg -> Maybe Int ++sseRegNum (FloatReg i) = Just i ++sseRegNum (DoubleReg i) = Just i ++sseRegNum (XmmReg i) = Just i ++sseRegNum (YmmReg i) = Just i ++sseRegNum (ZmmReg i) = Just i ++sseRegNum _ = Nothing ++ ++-- the bool indicates whether the global reg was added as padding. ++-- the returned list is not sorted in any particular order, ++-- but does indicate the set of live registers needed, with SSE padding. ++padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)] ++padLiveArgs live = allRegs ++ where ++ sseRegNums = sort $ mapMaybe sseRegNum live ++ (_, padding) = foldl assignSlots (1, []) $ sseRegNums ++ allRegs = padding ++ map (\r -> (False, r)) live ++ ++ assignSlots (i, acc) regNum ++ | i == regNum = -- don't need padding here ++ (i+1, acc) ++ | i < regNum = let -- add padding for slots i .. regNum-1 ++ numNeeded = regNum-i ++ acc' = genPad i numNeeded ++ acc ++ in ++ (regNum+1, acc') ++ | otherwise = error "padLiveArgs -- i > regNum ??" ++ ++ genPad start n = ++ take n $ flip map (iterate (+1) start) (\i -> ++ (True, FloatReg i)) ++ -- NOTE: Picking float should be fine for the following reasons: ++ -- (1) Float aliases with all the other SSE register types on ++ -- the given platform. ++ -- (2) The argument is not live anyways. ++ + + -- | Llvm standard fun attributes + llvmStdFunAttrs :: [LlvmFuncAttr] +diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +index e812dd445f1..a7121b7909a 100644 +--- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs ++++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs +@@ -14,7 +14,7 @@ import LlvmCodeGen.Base + import LlvmCodeGen.Regs + + import BlockId +-import CodeGen.Platform ( activeStgRegs, callerSaves ) ++import CodeGen.Platform ( activeStgRegs ) + import CLabel + import Cmm + import PprCmm +@@ -211,7 +211,6 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args + fptr <- liftExprData $ getFunPtr funTy t + argVars' <- castVarsW Signed $ zip argVars argTy + +- doTrashStmts + let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1] + statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) [] + | otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt) +@@ -294,7 +293,6 @@ genCall t@(PrimTarget op) [] args + fptr <- getFunPtrW funTy t + argVars' <- castVarsW Signed $ zip argVars argTy + +- doTrashStmts + let alignVal = mkIntLit i32 align + arguments = argVars' ++ (alignVal:isVolVal) + statement $ Expr $ Call StdCall fptr arguments [] +@@ -446,7 +444,6 @@ genCall target res args = runStmtsDecls $ do + | never_returns = statement $ Unreachable + | otherwise = return () + +- doTrashStmts + + -- make the actual call + case retTy of +@@ -1759,12 +1756,9 @@ genLit _ CmmHighStackMark + funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData + funPrologue live cmmBlocks = do + +- trash <- getTrashRegs + let getAssignedRegs :: CmmNode O O -> [CmmReg] + getAssignedRegs (CmmAssign reg _) = [reg] +- -- Calls will trash all registers. Unfortunately, this needs them to +- -- be stack-allocated in the first place. +- getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs ++ getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs + getAssignedRegs _ = [] + getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body + assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks +@@ -1794,14 +1788,9 @@ funPrologue live cmmBlocks = do + funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements) + funEpilogue live = do + +- -- Have information and liveness optimisation is enabled? +- let liveRegs = alwaysLive ++ live +- isSSE (FloatReg _) = True +- isSSE (DoubleReg _) = True +- isSSE (XmmReg _) = True +- isSSE (YmmReg _) = True +- isSSE (ZmmReg _) = True +- isSSE _ = False ++ -- the bool indicates whether the register is padding. ++ let alwaysNeeded = map (\r -> (False, r)) alwaysLive ++ livePadded = alwaysNeeded ++ padLiveArgs live + + -- Set to value or "undef" depending on whether the register is + -- actually live +@@ -1813,39 +1802,17 @@ funEpilogue live = do + let ty = (pLower . getVarType $ lmGlobalRegVar dflags r) + return (Just $ LMLitVar $ LMUndefLit ty, nilOL) + platform <- getDynFlag targetPlatform +- loads <- flip mapM (activeStgRegs platform) $ \r -> case () of +- _ | r `elem` liveRegs -> loadExpr r +- | not (isSSE r) -> loadUndef r ++ let allRegs = activeStgRegs platform ++ loads <- flip mapM allRegs $ \r -> case () of ++ _ | (False, r) `elem` livePadded ++ -> loadExpr r -- if r is not padding, load it ++ | not (isSSE r) || (True, r) `elem` livePadded ++ -> loadUndef r + | otherwise -> return (Nothing, nilOL) + + let (vars, stmts) = unzip loads + return (catMaybes vars, concatOL stmts) + +- +--- | A series of statements to trash all the STG registers. +--- +--- In LLVM we pass the STG registers around everywhere in function calls. +--- So this means LLVM considers them live across the entire function, when +--- in reality they usually aren't. For Caller save registers across C calls +--- the saving and restoring of them is done by the Cmm code generator, +--- using Cmm local vars. So to stop LLVM saving them as well (and saving +--- all of them since it thinks they're always live, we trash them just +--- before the call by assigning the 'undef' value to them. The ones we +--- need are restored from the Cmm local var and the ones we don't need +--- are fine to be trashed. +-getTrashStmts :: LlvmM LlvmStatements +-getTrashStmts = do +- regs <- getTrashRegs +- stmts <- flip mapM regs $ \ r -> do +- reg <- getCmmReg (CmmGlobal r) +- let ty = (pLower . getVarType) reg +- return $ Store (LMLitVar $ LMUndefLit ty) reg +- return $ toOL stmts +- +-getTrashRegs :: LlvmM [GlobalReg] +-getTrashRegs = do plat <- getLlvmPlatform +- return $ filter (callerSaves plat) (activeStgRegs plat) +- + -- | Get a function pointer to the CLabel specified. + -- + -- This is for Haskell functions, function type is assumed, so doesn't work +@@ -1967,7 +1934,3 @@ getCmmRegW = lift . getCmmReg + genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar + genLoadW atomic e ty = liftExprData $ genLoad atomic e ty + +-doTrashStmts :: WriterT LlvmAccum LlvmM () +-doTrashStmts = do +- stmts <- lift getTrashStmts +- tell $ LlvmAccum stmts mempty +diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs +index 86dd913461c..f4d5e7f553c 100644 +--- a/compiler/main/DriverPipeline.hs ++++ b/compiler/main/DriverPipeline.hs +@@ -1465,7 +1465,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags + -- we always (unless -optlo specified) run Opt since we rely on it to + -- fix up some pretty big deficiencies in the code we generate + llvmOpts = case optLevel dflags of +- 0 -> "-mem2reg -globalopt" ++ 0 -> "-mem2reg -globalopt -lower-expect" + 1 -> "-O1 -globalopt" + _ -> "-O2" + diff --git a/D4159.patch b/D4159.patch deleted file mode 100644 index 17db2f3..0000000 --- a/D4159.patch +++ /dev/null @@ -1,70 +0,0 @@ -diff --git a/utils/ghc-pkg/Main.hs b/utils/ghc-pkg/Main.hs ---- a/utils/ghc-pkg/Main.hs -+++ b/utils/ghc-pkg/Main.hs -@@ -1208,7 +1208,18 @@ - pkgsCabalFormat = packages db - - pkgsGhcCacheFormat :: [PackageCacheFormat] -- pkgsGhcCacheFormat = map convertPackageInfoToCacheFormat pkgsCabalFormat -+ pkgsGhcCacheFormat -+ = map (recomputeValidAbiDeps pkgsCabalFormat) -- Note [Recompute abi-depends] -+ $ map convertPackageInfoToCacheFormat -+ pkgsCabalFormat -+ -+ hasAnyAbiDepends :: InstalledPackageInfo -> Bool -+ hasAnyAbiDepends x = length (abiDepends x) > 0 -+ -+-- -- warn when we find any (possibly-)bogus abi-depends fields; -+-- -- Note [Recompute abi-depends] -+-- when (any hasAnyAbiDepends pkgsCabalFormat) $ -+-- infoLn "ignoring (possibly broken) abi-depends field for packages" - - when (verbosity > Normal) $ - infoLn ("writing cache " ++ filename) -@@ -1231,6 +1242,45 @@ - ModuleName - OpenModule - -+{- Note [Recompute abi-depends] -+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ -+ -+Like most fields, `ghc-pkg` relies on who-ever is performing package -+registration to fill in fields; this includes the `abi-depends` field present -+for the package. -+ -+However, this was likely a mistake, and is not very robust; in certain cases, -+versions of Cabal may use bogus abi-depends fields for a package when doing -+builds. Why? Because package database information is aggressively cached; it is -+possible to work Cabal into a situation where it uses a cached version of -+`abi-depends`, rather than the one in the actual database after it has been -+recomputed. -+ -+However, there is an easy fix: ghc-pkg /already/ knows the `abi-depends` of a -+package, because they are the ABIs of the packages pointed at by the `depends` -+field. So it can simply look up the abi from the dependencies in the original -+database, and ignore whatever the system registering gave it. -+ -+So, instead, we do two things here: -+ -+ - We throw away the information for a registered package's `abi-depends` field. -+ -+ - We recompute it: we simply look up the unit ID of the package in the original -+ database, and use *its* abi-depends. -+ -+See Trac #14381, and Cabal issue #4728. -+ -+-} -+ -+recomputeValidAbiDeps :: [InstalledPackageInfo] -> PackageCacheFormat -> PackageCacheFormat -+recomputeValidAbiDeps db pkg = pkg { GhcPkg.abiDepends = catMaybes (newAbiDeps) } -+ where -+ newAbiDeps = flip map (GhcPkg.abiDepends pkg) $ \(k, _) -> -+ case filter (\d -> installedUnitId d == k) db of -+ [] -> Nothing -+ [x] -> Just (k, unAbiHash (abiHash x)) -+ _ -> Nothing -- ??? -+ - convertPackageInfoToCacheFormat :: InstalledPackageInfo -> PackageCacheFormat - convertPackageInfoToCacheFormat pkg = - GhcPkg.InstalledPackageInfo { - diff --git a/ghc-Debian-buildpath-abi-stability.patch b/buildpath-abi-stability.patch similarity index 100% rename from ghc-Debian-buildpath-abi-stability.patch rename to buildpath-abi-stability.patch diff --git a/fix-build-using-unregisterized-v8.2.patch b/fix-build-using-unregisterized-v8.2.patch new file mode 100644 index 0000000..29d7b49 --- /dev/null +++ b/fix-build-using-unregisterized-v8.2.patch @@ -0,0 +1,51 @@ +Description: Allow unregisterised ghc-8.2 to build newer GHC + Commit b68697e579d38ca29c2b84377dc2affa04659a28 introduced a regression + stopping existing unregisteristed compilers from being used to compile a newer + version of GHC. The problem is that the bootstrap compiler uses the newer Stg.h + where EB_, IB_, etc, definitions have changed resulting in the following error: +. + error: conflicting types for 'ghc_GhcPrelude_zdtrModule4_bytes' + note: in definition of macro 'EB_' + #define EB_(X) extern const char X[] + note: previous definition of 'ghc_GhcPrelude_zdtrModule4_bytes' was here + char ghc_GhcPrelude_zdtrModule4_bytes[] = "ghc"; +. + For more information about the problem, see https://phabricator.haskell.org/D4114. +. + This patch is a rework of https://phabricator.haskell.org/D3741. + It modifies Stg.h to include the old definitions, if a compiler older than + 8.4 is being used. +. + This patch can be removed, once ghc-8.2 is no longer the bootstrap compiler. +Author: Ilias Tsitsimpis +Bug: https://ghc.haskell.org/trac/ghc/ticket/15201 + +Index: b/includes/Stg.h +=================================================================== +--- a/includes/Stg.h ++++ b/includes/Stg.h +@@ -232,6 +232,16 @@ typedef StgInt I_; + typedef StgWord StgWordArray[]; + typedef StgFunPtr F_; + ++#if __GLASGOW_HASKELL__ < 804 ++#define EB_(X) extern char X[] ++#define IB_(X) static char X[] ++#define EI_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) ++#define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) ++#define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) ++#define FN_(f) StgFunPtr f(void) ++#define EF_(f) StgFunPtr f(void) /* External Cmm functions */ ++#define EFF_(f) void f() /* See Note [External function prototypes] */ ++#else + /* byte arrays (and strings): */ + #define EB_(X) extern const char X[] + #define IB_(X) static const char X[] +@@ -250,6 +260,7 @@ typedef StgFunPtr F_; + #define EF_(f) StgFunPtr f(void) /* External Cmm functions */ + /* foreign functions: */ + #define EFF_(f) void f() /* See Note [External function prototypes] */ ++#endif /* __GLASGOW_HASKELL__ < 804 */ + + /* Note [External function prototypes] See Trac #8965, #11395 + ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch b/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch deleted file mode 100644 index c44a21f..0000000 --- a/ghc-7.8-arm7_saner-linker-opt-handling-9873.patch +++ /dev/null @@ -1,78 +0,0 @@ -On ARM, we want to make sure that GHC uses the gold linker. - -In order to achieve that, we need to get `-fuse-ld=gold` into -SettingsCCompilerLinkFlags in the settings. - -This field is filled with only CONF_GCC_LINKER_OPTS_STAGE2. So we want that -flag to show up there. - -But this variable is used in a few other cases (LDFLAGS, options to hsc2hs) -where -fuse-ld=gold caused problems. -(These problems were not investigated. Maybe _they_ could be solved?) - -So as a work-around we remove any other use of CONF_GCC_LINKER_OPTS_STAGE2. - - -Index: ghc-7.8.3.20141119/libffi/ghc.mk -=================================================================== ---- ghc-7.8.3.20141119.orig/libffi/ghc.mk 2014-04-07 20:26:08.000000000 +0200 -+++ ghc-7.8.3.20141119/libffi/ghc.mk 2014-12-08 18:57:03.392339809 +0100 -@@ -88,7 +88,7 @@ - NM=$(NM) \ - RANLIB=$(REAL_RANLIB_CMD) \ - CFLAGS="$(SRC_CC_OPTS) $(CONF_CC_OPTS_STAGE1) -w" \ -- LDFLAGS="$(SRC_LD_OPTS) $(CONF_GCC_LINKER_OPTS_STAGE1) -w" \ -+ LDFLAGS="$(SRC_LD_OPTS) -w" \ - "$(SHELL)" ./configure \ - --prefix=$(TOP)/libffi/build/inst \ - --libdir=$(TOP)/libffi/build/inst/lib \ -Index: ghc-7.8.3.20141119/mk/config.mk.in -=================================================================== ---- ghc-7.8.3.20141119.orig/mk/config.mk.in 2014-12-08 18:49:28.215171926 +0100 -+++ ghc-7.8.3.20141119/mk/config.mk.in 2014-12-08 18:57:20.637055726 +0100 -@@ -570,7 +570,6 @@ - # $1 = stage - SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(filter-out -O,$$(SRC_CC_OPTS) $$(CONF_CC_OPTS_STAGE$1))) - SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --cflag=,$$(CONF_CPP_OPTS_STAGE$1)) --SRC_HSC2HS_OPTS_STAGE$1 += $$(addprefix --lflag=,$$(CONF_GCC_LINKER_OPTS_STAGE$1)) - endef - $(eval $(call set_stage_HSC2HS_OPTS,0)) - $(eval $(call set_stage_HSC2HS_OPTS,1)) -Index: ghc-7.8.3.20141119/rules/build-package-data.mk -=================================================================== ---- ghc-7.8.3.20141119.orig/rules/build-package-data.mk 2014-04-14 14:38:12.000000000 +0200 -+++ ghc-7.8.3.20141119/rules/build-package-data.mk 2014-12-08 18:57:49.366250332 +0100 -@@ -50,7 +50,7 @@ - # for a feature it may not generate warning-free C code, and thus may - # think that the feature doesn't exist if -Werror is on. - $1_$2_CONFIGURE_CFLAGS = $$(filter-out -Werror,$$(SRC_CC_OPTS)) $$(CONF_CC_OPTS_STAGE$3) $$($1_CC_OPTS) $$($1_$2_CC_OPTS) $$(SRC_CC_WARNING_OPTS) --$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$(CONF_GCC_LINKER_OPTS_STAGE$3) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) -+$1_$2_CONFIGURE_LDFLAGS = $$(SRC_LD_OPTS) $$($1_LD_OPTS) $$($1_$2_LD_OPTS) - $1_$2_CONFIGURE_CPPFLAGS = $$(SRC_CPP_OPTS) $$(CONF_CPP_OPTS_STAGE$3) $$($1_CPP_OPTS) $$($1_$2_CPP_OPTS) - - $1_$2_CONFIGURE_OPTS += --configure-option=CFLAGS="$$($1_$2_CONFIGURE_CFLAGS)" -Index: ghc-7.8.3.20141119/rules/distdir-opts.mk -=================================================================== ---- ghc-7.8.3.20141119.orig/rules/distdir-opts.mk 2014-04-07 20:26:08.000000000 +0200 -+++ ghc-7.8.3.20141119/rules/distdir-opts.mk 2014-12-08 18:58:18.435461083 +0100 -@@ -64,7 +64,6 @@ - endif - - $1_$2_DIST_LD_OPTS = \ -- $$(CONF_GCC_LINKER_OPTS_STAGE$3) \ - $$(SRC_LD_OPTS) \ - $$($1_LD_OPTS) \ - $$($1_$2_LD_OPTS) \ -Index: ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk -=================================================================== ---- ghc-7.8.3.20141119.orig/utils/hsc2hs/ghc.mk 2014-04-07 20:26:15.000000000 +0200 -+++ ghc-7.8.3.20141119/utils/hsc2hs/ghc.mk 2014-12-08 18:57:07.848524715 +0100 -@@ -27,7 +27,7 @@ - # system uses it for all stages and passes the right options for each stage - # on the command line - define utils/hsc2hs_dist-install_SHELL_WRAPPER_EXTRA --echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1)) $(addprefix --lflag=,$(CONF_GCC_LINKER_OPTS_STAGE1))"' >> "$(WRAPPER)" -+echo 'HSC2HS_EXTRA="$(addprefix --cflag=,$(CONF_CC_OPTS_STAGE1))"' >> "$(WRAPPER)" - endef - - ifneq "$(BINDIST)" "YES" diff --git a/ghc-Cabal-install-PATH-warning.patch b/ghc-Cabal-install-PATH-warning.patch index 5081fa1..786c5d9 100644 --- a/ghc-Cabal-install-PATH-warning.patch +++ b/ghc-Cabal-install-PATH-warning.patch @@ -1,20 +1,12 @@ ---- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 16:51:43.000000000 +0200 -+++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-01-23 23:05:47.047081056 +0100 -@@ -36,7 +36,7 @@ - import Distribution.Simple.Utils - ( createDirectoryIfMissingVerbose - , installDirectoryContents, installOrdinaryFile, isInSearchPath -- , die', info, noticeNoWrap, warn, matchDirFileGlob ) -+ , die', info, noticeNoWrap, warn, matchDirFileGlob, debug ) - import Distribution.Simple.Compiler - ( CompilerFlavor(..), compilerFlavor ) - import Distribution.Simple.Setup -@@ -215,7 +215,7 @@ +--- ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs~ 2017-05-05 23:51:43.000000000 +0900 ++++ ghc-8.2.2/libraries/Cabal/Cabal/Distribution/Simple/Install.hs 2018-02-27 12:22:13.159432104 +0900 +@@ -215,8 +215,7 @@ ++ " in " ++ binPref) inPath <- isInSearchPath binPref when (not inPath) $ - warn verbosity ("The directory " ++ binPref -+ debug verbosity ("The directory " ++ binPref - ++ " is not in the system search path.") +- ++ " is not in the system search path.") ++ warn verbosity ("Executable installed in " ++ binPref) case compilerFlavor (compiler lbi) of GHC -> GHC.installExe verbosity lbi binPref buildPref progFix pkg_descr exe + GHCJS -> GHCJS.installExe verbosity lbi binPref buildPref progFix pkg_descr exe diff --git a/ghc-Debian-reproducible-tmp-names.patch b/ghc-Debian-reproducible-tmp-names.patch deleted file mode 100644 index 16ffc32..0000000 --- a/ghc-Debian-reproducible-tmp-names.patch +++ /dev/null @@ -1,43 +0,0 @@ -This is an attempt to make GHC build reproducible. The name of .c files may end -up in the resulting binary (in the debug section), but not the directory. - -Instead of using the process id, create a hash from the command line arguments, -and assume that is going to be unique. - -Index: ghc-8.0.2/compiler/main/SysTools.hs -=================================================================== ---- ghc-8.0.2.orig/compiler/main/SysTools.hs -+++ ghc-8.0.2/compiler/main/SysTools.hs -@@ -65,6 +65,7 @@ - import Util - import DynFlags - import Exception -+import Fingerprint - - import LlvmCodeGen.Base (llvmVersionStr, supportedLlvmVersion) - -@@ -1145,8 +1146,8 @@ - mapping <- readIORef dir_ref - case Map.lookup tmp_dir mapping of - Nothing -> do -- pid <- getProcessID -- let prefix = tmp_dir "ghc" ++ show pid ++ "_" -+ pid <- getStableProcessID -+ let prefix = tmp_dir "ghc" ++ pid ++ "_" - mask_ $ mkTempDir prefix - Just dir -> return dir - where -@@ -1562,6 +1563,13 @@ - getProcessID = System.Posix.Internals.c_getpid >>= return . fromIntegral - #endif - -+-- Debian-specific hack to get reproducible output, by not using the "random" -+-- pid, but rather something determinisic -+getStableProcessID :: IO String -+getStableProcessID = do -+ args <- getArgs -+ return $ take 4 $ show $ fingerprintString $ unwords args -+ - -- Divvy up text stream into lines, taking platform dependent - -- line termination into account. - linesPlatform :: String -> [String] diff --git a/ghc.spec b/ghc.spec index 99216be..0099070 100644 --- a/ghc.spec +++ b/ghc.spec @@ -26,20 +26,20 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.2 needs llvm-3.9 -%global llvm_major 3.9 +# 8.4 needs llvm-5.0 +%global llvm_major 5.0 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc # ghc must be rebuilt after a version bump to avoid ABI change problems -Version: 8.2.2 +Version: 8.4.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 72%{?dist} +Release: 73%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -56,10 +56,6 @@ Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch -# https://github.com/haskell/cabal/issues/4728 -# https://ghc.haskell.org/trac/ghc/ticket/14381 -# https://phabricator.haskell.org/D4159 -Patch4: D4159.patch # https://github.com/ghc/ghc/pull/143 Patch5: ghc-configure-fix-sphinx-version-check.patch @@ -69,11 +65,15 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch +# revert 8.4.4 llvm changes +# https://ghc.haskell.org/trac/ghc/ticket/15780 +Patch16: https://github.com/ghc/ghc/commit/6e361d895dda4600a85e01c72ff219474b5c7190.patch + # Debian patches: -Patch24: ghc-Debian-buildpath-abi-stability.patch -Patch26: ghc-Debian-no-missing-haddock-file-warning.patch -Patch27: ghc-Debian-reproducible-tmp-names.patch -Patch28: ghc-Debian-x32-use-native-x86_64-insn.patch +Patch24: buildpath-abi-stability.patch +Patch26: no-missing-haddock-file-warning.patch +Patch28: x32-use-native-x86_64-insn.patch +Patch30: fix-build-using-unregisterized-v8.2.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -85,13 +85,14 @@ BuildRequires: ghc-compiler %if %{with abicheck} BuildRequires: ghc %endif -BuildRequires: ghc-rpm-macros-extra >= 1.8 +BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel +BuildRequires: ghc-transformers-devel BuildRequires: gmp-devel BuildRequires: libffi-devel # for terminfo @@ -216,35 +217,36 @@ This package provides the User Guide and Haddock manual. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-2.0.1.0 +%ghc_lib_subpackage -d -l BSD Cabal-2.2.0.1 %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.10.1.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.11.1.0 %ghc_lib_subpackage -d -l BSD binary-0.8.5.1 %ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.10.2 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.11.0 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.3.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.0.2 -%ghc_lib_subpackage -d -l BSD filepath-1.4.1.2 -%define ghc_pkg_obsoletes ghc-bin-package-db-devel < 0.0.0.0-12 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.1.5 +%ghc_lib_subpackage -d -l BSD filepath-1.4.2 # in ghc not ghc-libraries: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} -%undefine ghc_pkg_obsoletes %ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 %ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.0 -%ghc_lib_subpackage -d -l BSD hoopl-3.10.2.2 +%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.2 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 -%ghc_lib_subpackage -d -l BSD pretty-1.1.3.3 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.1.0 -%ghc_lib_subpackage -d -l BSD template-haskell-2.12.0.0 -%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.0 +%ghc_lib_subpackage -d -l BSD mtl-2.2.2 +%ghc_lib_subpackage -d -l BSD parsec-3.1.13.0 +%ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.3.0 +%ghc_lib_subpackage -d -l BSD stm-2.4.5.1 +%ghc_lib_subpackage -d -l BSD template-haskell-2.13.0.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.1 +%ghc_lib_subpackage -d -l BSD text-1.2.3.1 %ghc_lib_subpackage -d -l BSD time-1.8.0.2 -%ghc_lib_subpackage -d -l BSD transformers-0.5.2.0 +%ghc_lib_subpackage -d -l BSD transformers-0.5.5.0 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{with docs} -%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2 +%ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1 %endif %endif @@ -273,7 +275,6 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %patch1 -p1 -b .orig %patch2 -p1 -b .orig -%patch4 -p1 -b .orig %patch5 -p1 -b .orig %if 0%{?fedora} || 0%{?rhel} > 6 @@ -288,10 +289,16 @@ rm -r libffi-tarballs %patch15 -p1 -b .orig %endif +%ifarch armv7hl aarch64 +%patch16 -p1 -b .orig -R +%endif + %patch24 -p1 -b .orig %patch26 -p1 -b .orig -%patch27 -p1 -b .orig %patch28 -p1 -b .orig +%ifarch s390x +%patch30 -p1 -b .orig +%endif %global gen_contents_index gen_contents_index.orig %if %{with docs} @@ -354,7 +361,6 @@ export CC=%{_bindir}/gcc --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --docdir=%{_docdir}/ghc \ - --with-llc=%{_bindir}/llc-%{llvm_major} --with-opt=%{_bindir}/opt-%{llvm_major} \ %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif @@ -379,6 +385,7 @@ done for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_libdir}!' $i done +sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %endif for i in %{ghc_packages_list}; do @@ -397,8 +404,8 @@ echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.5.1.1 -%ghc_gen_filelists integer-gmp 1.0.1.0 +%ghc_gen_filelists ghc-prim 0.5.2.0 +%ghc_gen_filelists integer-gmp 1.0.2.0 %define merge_filelist()\ cat ghc-%1.files >> ghc-%2.files\ @@ -584,6 +591,7 @@ fi %{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt +%{ghclibdir}/llvm-targets %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache %{ghclibdir}/package.conf.d/package.cache.lock @@ -610,12 +618,14 @@ fi %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/prologue.txt %ghost %{ghc_html_dir}/libraries/doc-index*.html +%ghost %{ghc_html_dir}/libraries/haddock-bundle.min.js %ghost %{ghc_html_dir}/libraries/haddock-util.js %ghost %{ghc_html_dir}/libraries/hslogo-16.png %ghost %{ghc_html_dir}/libraries/index*.html %ghost %{ghc_html_dir}/libraries/minus.gif %ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif +%ghost %{ghc_html_dir}/libraries/quick-jump.css %ghost %{ghc_html_dir}/libraries/synopsis.png %dir %{_localstatedir}/lib/ghc %ghost %{_localstatedir}/lib/ghc/pkg-dir.cache @@ -643,6 +653,17 @@ fi %changelog +* Sat Feb 16 2019 Jens Petersen - 8.4.4-73 +- update to GHC 8.4 +- https://ghc.haskell.org/trac/ghc/blog/ghc-8.4.1-released +- new patches: + - 6e361d895dda4600a85e01c72ff219474b5c7190.patch + - fix-build-using-unregisterized-v8.2.patch +- dropped patch: + - D4159.patch + - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch + - ghc-Debian-reproducible-tmp-names.patch + * Fri Feb 8 2019 Jens Petersen - 8.2.2-72 - add ghc_unregisterized_arches - Recommends zlib-devel diff --git a/ghc-Debian-no-missing-haddock-file-warning.patch b/no-missing-haddock-file-warning.patch similarity index 100% rename from ghc-Debian-no-missing-haddock-file-warning.patch rename to no-missing-haddock-file-warning.patch diff --git a/sources b/sources index 6b499bd..a6f24f6 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -SHA512 (ghc-8.2.2-src.tar.xz) = 6549416f470b599973d409fa45f59c25b07e6a94798cef1a19ad432547dc225338cf4dbc4a4793114b4a417798a3b59b122b92b020251074405c5302b7ffe799 -SHA512 (ghc-8.2.2-testsuite.tar.xz) = 5b60413910bce2ef0d71e2f531d7297cefc0b03df3e23d63f7a872d9a264e1512b2d6631a3fba35e72d113389762ba34d503649ea4a852ce9fd42e94ef6b96dc +SHA512 (ghc-8.4.4-src.tar.xz) = 685e102eee8cf8b6a377afd7871998c8c368a5da288469367e3fb804aa6109e6f59be5945b8cd3d1e36c851190ea9a7f74c576528589589313d237b721d86da5 diff --git a/ghc-Debian-x32-use-native-x86_64-insn.patch b/x32-use-native-x86_64-insn.patch similarity index 100% rename from ghc-Debian-x32-use-native-x86_64-insn.patch rename to x32-use-native-x86_64-insn.patch From c149b76c5a6b3dbc5155b10e85e901e53e1fc998 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 16 Feb 2019 01:30:47 +0800 Subject: [PATCH 481/530] add upstream fix for sphinx-1.8 --- ghc-sphinx-1.8-4eebc8016.patch | 46 ++++++++++++++++++++++++++++++++++ ghc.spec | 5 ++++ 2 files changed, 51 insertions(+) create mode 100644 ghc-sphinx-1.8-4eebc8016.patch diff --git a/ghc-sphinx-1.8-4eebc8016.patch b/ghc-sphinx-1.8-4eebc8016.patch new file mode 100644 index 0000000..155be14 --- /dev/null +++ b/ghc-sphinx-1.8-4eebc8016.patch @@ -0,0 +1,46 @@ +commit 4eebc8016f68719e1ccdf460754a97d1f4d6ef05 +Author: Ben Gamari +Date: Thu Sep 20 08:27:37 2018 -0400 + + users-guide: Fix build with sphinx 1.8 + + It seems that both add_object_type and add_directive_to_domain both register a + directive. Previously sphinx didn't seem to mind this but as of Sphinx 1.8 it + crashes with an exception. + +diff --git a/docs/users_guide/flags.py b/docs/users_guide/flags.py +index a70f7fef1e..284b5e06cc 100644 +--- a/docs/users_guide/flags.py ++++ b/docs/users_guide/flags.py +@@ -48,6 +48,8 @@ from docutils import nodes + from docutils.parsers.rst import Directive, directives + from sphinx import addnodes + from sphinx.domains.std import GenericObject ++from sphinx.domains import ObjType ++from sphinx.roles import XRefRole + from sphinx.errors import SphinxError + from utils import build_table_from_list + +@@ -599,14 +601,20 @@ def purge_flags(app, env, docname): + ### Initialization + + def setup(app): ++ # Yuck: We can't use app.add_object_type since we need to provide the ++ # Directive instance ourselves. ++ std_object_types = app.registry.domain_object_types.setdefault('std', {}) + + # Add ghc-flag directive, and override the class with our own +- app.add_object_type('ghc-flag', 'ghc-flag') + app.add_directive_to_domain('std', 'ghc-flag', Flag) ++ app.add_role_to_domain('std', 'ghc-flag', XRefRole()) ++ std_object_types['ghc-flag'] = ObjType('ghc-flag', 'ghc-flag') + + # Add extension directive, and override the class with our own +- app.add_object_type('extension', 'extension') + app.add_directive_to_domain('std', 'extension', LanguageExtension) ++ app.add_role_to_domain('std', 'extension', XRefRole()) ++ std_object_types['extension'] = ObjType('ghc-flag', 'ghc-flag') ++ + # NB: language-extension would be misinterpreted by sphinx, and produce + # lang="extensions" XML attributes + diff --git a/ghc.spec b/ghc.spec index 0099070..ea83881 100644 --- a/ghc.spec +++ b/ghc.spec @@ -58,7 +58,10 @@ Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch # https://github.com/ghc/ghc/pull/143 Patch5: ghc-configure-fix-sphinx-version-check.patch +# https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 +Patch6: ghc-sphinx-1.8-4eebc8016.patch +# Arch dependent packages Patch12: ghc-armv7-VFPv3D16--NEON.patch # for s390x @@ -276,6 +279,7 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %patch2 -p1 -b .orig %patch5 -p1 -b .orig +%patch6 -p1 -b .orig %if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs @@ -659,6 +663,7 @@ fi - new patches: - 6e361d895dda4600a85e01c72ff219474b5c7190.patch - fix-build-using-unregisterized-v8.2.patch + - ghc-sphinx-1.8-4eebc8016.patch - dropped patch: - D4159.patch - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch From 8baf63924cc5c03b509cf4eee076ebc07a33d015 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 16 Feb 2019 07:50:45 +0800 Subject: [PATCH 482/530] leave stripping to rpm --- ghc.spec | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index ea83881..a024873 100644 --- a/ghc.spec +++ b/ghc.spec @@ -456,8 +456,6 @@ for i in hsc2hs runhaskell; do touch %{buildroot}%{_bindir}/$i done -%ghc_strip_dynlinked - %if %{with docs} mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index @@ -668,6 +666,7 @@ fi - D4159.patch - ghc-7.8-arm7_saner-linker-opt-handling-9873.patch - ghc-Debian-reproducible-tmp-names.patch +- rely on rpm to strip * Fri Feb 8 2019 Jens Petersen - 8.2.2-72 - add ghc_unregisterized_arches From 31428bc0399cd60105e8f994baaebec4dfe38afd Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 4 Mar 2019 14:00:41 +0800 Subject: [PATCH 483/530] fix 32bit adjacent floats on 64bit unregisterized upstream patch for https://ghc.haskell.org/trac/ghc/ticket/15853 --- ...97782b6b0a252da7fdcf4921198ad4e1d96c.patch | 69 +++++++++++++++++++ ghc.spec | 10 ++- 2 files changed, 78 insertions(+), 1 deletion(-) create mode 100644 35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch diff --git a/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch b/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch new file mode 100644 index 0000000..3a297c7 --- /dev/null +++ b/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch @@ -0,0 +1,69 @@ +From 35a897782b6b0a252da7fdcf4921198ad4e1d96c Mon Sep 17 00:00:00 2001 +From: James Clarke +Date: Thu, 22 Nov 2018 11:55:17 -0500 +Subject: [PATCH] UNREG: PprC: Add support for adjacent floats + +When two 32-bit floats are adjacent for a 64-bit target, there is no +padding between them to force alignment, so we must combine their bit +representations into a single word. + +Reviewers: bgamari, simonmar + +Reviewed By: simonmar + +Subscribers: rwbarton, carter + +GHC Trac Issues: #15853 + +Differential Revision: https://phabricator.haskell.org/D5306 +--- + compiler/cmm/PprC.hs | 24 +++++++++++++++++++++++- + 1 file changed, 23 insertions(+), 1 deletion(-) + +diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs +index 17fef7fc97..6ebfd20291 100644 +--- a/compiler/cmm/PprC.hs ++++ b/compiler/cmm/PprC.hs +@@ -512,9 +512,12 @@ pprLit1 other = pprLit other + pprStatics :: DynFlags -> [CmmStatic] -> [SDoc] + pprStatics _ [] = [] + pprStatics dflags (CmmStaticLit (CmmFloat f W32) : rest) +- -- floats are padded to a word by padLitToWord, see #1852 ++ -- odd numbers of floats are padded to a word by mkVirtHeapOffsetsWithPadding + | wORD_SIZE dflags == 8, CmmStaticLit (CmmInt 0 W32) : rest' <- rest + = pprLit1 (floatToWord dflags f) : pprStatics dflags rest' ++ -- adjacent floats aren't padded but combined into a single word ++ | wORD_SIZE dflags == 8, CmmStaticLit (CmmFloat g W32) : rest' <- rest ++ = pprLit1 (floatPairToWord dflags f g) : pprStatics dflags rest' + | wORD_SIZE dflags == 4 + = pprLit1 (floatToWord dflags f) : pprStatics dflags rest + | otherwise +@@ -1270,6 +1273,25 @@ floatToWord dflags r + , wORDS_BIGENDIAN dflags = 32 + | otherwise = 0 + ++floatPairToWord :: DynFlags -> Rational -> Rational -> CmmLit ++floatPairToWord dflags r1 r2 ++ = runST (do ++ arr <- newArray_ ((0::Int),1) ++ writeArray arr 0 (fromRational r1) ++ writeArray arr 1 (fromRational r2) ++ arr' <- castFloatToWord32Array arr ++ w32_1 <- readArray arr' 0 ++ w32_2 <- readArray arr' 1 ++ return (pprWord32Pair w32_1 w32_2) ++ ) ++ where pprWord32Pair w32_1 w32_2 ++ | wORDS_BIGENDIAN dflags = ++ CmmInt ((shiftL i1 32) .|. i2) W64 ++ | otherwise = ++ CmmInt ((shiftL i2 32) .|. i1) W64 ++ where i1 = toInteger w32_1 ++ i2 = toInteger w32_2 ++ + doubleToWords :: DynFlags -> Rational -> [CmmLit] + doubleToWords dflags r + = runST (do +-- +2.19.2 + diff --git a/ghc.spec b/ghc.spec index a024873..4496165 100644 --- a/ghc.spec +++ b/ghc.spec @@ -39,7 +39,7 @@ Version: 8.4.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 73%{?dist} +Release: 74%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -67,6 +67,9 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # for s390x # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch +# https://ghc.haskell.org/trac/ghc/ticket/15853 +# https://phabricator.haskell.org/D5306 (in 8.8) +Patch17: https://gitlab.haskell.org/ghc/ghc/commit/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch # revert 8.4.4 llvm changes # https://ghc.haskell.org/trac/ghc/ticket/15780 @@ -291,6 +294,7 @@ rm -r libffi-tarballs %ifarch s390x %patch15 -p1 -b .orig +%patch17 -p1 -b .orig %endif %ifarch armv7hl aarch64 @@ -655,6 +659,10 @@ fi %changelog +* Mon Mar 4 2019 Jens Petersen - 8.4.4-74 +- unregisterized: fix 32bit adjacent floats issue + (https://ghc.haskell.org/trac/ghc/ticket/15853) + * Sat Feb 16 2019 Jens Petersen - 8.4.4-73 - update to GHC 8.4 - https://ghc.haskell.org/trac/ghc/blog/ghc-8.4.1-released From d3aabb4ef98169c66106395124e8b6238957b170 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 28 Jun 2019 04:15:51 +0000 Subject: [PATCH 484/530] add transfiletriggers to replace individual post/postun scriptlets --- ghc.spec | 12 +++++++++++- 1 file changed, 11 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 4496165..a801f05 100644 --- a/ghc.spec +++ b/ghc.spec @@ -39,7 +39,7 @@ Version: 8.4.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 74%{?dist} +Release: 75%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -560,6 +560,13 @@ if [ "$1" = 0 ]; then update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc fi +%transfiletriggerin compiler -- %{ghclibdir}/package.conf.d +%ghc_pkg_recache +%end + +%transfiletriggerpostun compiler -- %{ghclibdir}/package.conf.d +%ghc_pkg_recache +%end %files @@ -659,6 +666,9 @@ fi %changelog +* Fri Jun 28 2019 Jens Petersen - 8.4.4-75 +- add transfiletriggers that will replace individual post/postun scriptlets + * Mon Mar 4 2019 Jens Petersen - 8.4.4-74 - unregisterized: fix 32bit adjacent floats issue (https://ghc.haskell.org/trac/ghc/ticket/15853) From 5d6a6f350aab7013007986895effd0faa40f3b69 Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Thu, 25 Jul 2019 01:58:32 +0000 Subject: [PATCH 485/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_31_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index a801f05..e794ced 100644 --- a/ghc.spec +++ b/ghc.spec @@ -39,7 +39,7 @@ Version: 8.4.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 75%{?dist} +Release: 76%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -666,6 +666,9 @@ fi %changelog +* Thu Jul 25 2019 Fedora Release Engineering +- Rebuilt for https://fedoraproject.org/wiki/Fedora_31_Mass_Rebuild + * Fri Jun 28 2019 Jens Petersen - 8.4.4-75 - add transfiletriggers that will replace individual post/postun scriptlets From 485a2897273d47a483675385992c4ab72814498e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 16 Jul 2019 16:23:37 +0000 Subject: [PATCH 486/530] major rework of ghc packaging: particularly prof and doc subpackages - bump release to 99 - drop ghc-doc-index script and cronjob - lock compiler to ghc-base-devel verrel - switch from %without_prof to %with_ghc_prof - split docs bcond to %with_haddock and %with_manual - disable debuginfo for quickbuild - BR ghc-rpm-macros 2.0 and make - allow python2-sphinx for current fedora releases - lighten ghc: only suggest ghc-doc, ghc-doc-index, ghc-manual, ghc-prof - drop support for rhel6 builds - use %ghc_set_gcc_flags - remove alternatives - filetriggers for haddock index updating - in future we might separate static devel subpackages too (if cabal can handle vanilla or dyn only) --- ghc-doc-index | 38 ------ ghc-doc-index.cron | 9 -- ghc.spec | 334 +++++++++++++++++++++------------------------ 3 files changed, 156 insertions(+), 225 deletions(-) delete mode 100755 ghc-doc-index delete mode 100755 ghc-doc-index.cron diff --git a/ghc-doc-index b/ghc-doc-index deleted file mode 100755 index a0223fa..0000000 --- a/ghc-doc-index +++ /dev/null @@ -1,38 +0,0 @@ -#!/bin/sh - -LOCKFILE=/var/lock/ghc-doc-index.lock - -# the lockfile is not meant to be perfect, it's just in case -# two cron scripts get run close to each other to keep -# them from stepping on each other's toes. -if [ -f $LOCKFILE ]; then - echo "Locked with $LOCKFILE" - exit 0 -fi - -if [ "$(id -u)" != "0" ]; then - echo Need to be root! - exit 1 -fi - -trap "{ rm -f $LOCKFILE ; exit 255; }" EXIT -touch $LOCKFILE - -PKGDIRCACHE=/var/lib/ghc/pkg-dir.cache -LISTING="env LANG=C ls -dl" - -# only re-index ghc docs when there are changes -cd /usr/share/doc/ghc/html/libraries -if [ -r "$PKGDIRCACHE" ]; then - $LISTING */ > $PKGDIRCACHE.new - DIR_DIFF=$(diff $PKGDIRCACHE $PKGDIRCACHE.new) -else - $LISTING */ > $PKGDIRCACHE -fi -if [ -x "gen_contents_index" -a ! -r "$PKGDIRCACHE.new" -o -n "$DIR_DIFF" ]; then - ./gen_contents_index -fi - -if [ -f $PKGDIRCACHE.new ]; then - mv -f $PKGDIRCACHE.new $PKGDIRCACHE -fi diff --git a/ghc-doc-index.cron b/ghc-doc-index.cron deleted file mode 100755 index 4efe2ff..0000000 --- a/ghc-doc-index.cron +++ /dev/null @@ -1,9 +0,0 @@ -#! /bin/bash -# updates the library documentation index after updates - -# This can be disabled by uninstalling ghc-doc-index -# or adding ghc-doc-index to "./jobs-deny". - -/usr/bin/ghc-doc-index - -exit 0 diff --git a/ghc.spec b/ghc.spec index e794ced..f4eba1a 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,5 +1,5 @@ -# disable prof, docs, perf build -# NB This SHOULD be disabled (bcond_with) for all koji production builds +# disable prof, docs, perf build, debuginfo +# NB This must be disabled (bcond_with) for all koji production builds %bcond_with quickbuild # make sure ghc libraries' ABI hashes unchanged @@ -8,18 +8,21 @@ # to handle RCs %global ghc_release %{version} +%global base_ver 4.11.1.0 + # build profiling libraries -# build docs (haddock and manuals) -# - combined since disabling haddock seems to cause no manuals built +# build haddock and manuals +# - earlier combined since disabling haddock seems to cause no manuals built? # - # perf production build (disable for quick build) %if %{with quickbuild} -%bcond_with prof -%bcond_with docs +%undefine with_ghc_prof +%undefine with_haddock +%bcond_with manual %bcond_with perf_build +%undefine _enable_debug_packages %else -%bcond_without prof -%bcond_without docs +%bcond_without manual %bcond_without perf_build %endif @@ -33,13 +36,12 @@ %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc -# ghc must be rebuilt after a version bump to avoid ABI change problems Version: 8.4.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 76%{?dist} +Release: 99%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -48,8 +50,6 @@ Source0: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-src.ta %if %{with testsuite} Source1: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-testsuite.tar.xz %endif -Source3: ghc-doc-index.cron -Source4: ghc-doc-index Source5: ghc-pkg.man Source6: haddock.man Source7: runghc.man @@ -61,7 +61,9 @@ Patch5: ghc-configure-fix-sphinx-version-check.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-sphinx-1.8-4eebc8016.patch -# Arch dependent packages +# Arch dependent patches + +# arm Patch12: ghc-armv7-VFPv3D16--NEON.patch # for s390x @@ -91,7 +93,7 @@ BuildRequires: ghc-compiler %if %{with abicheck} BuildRequires: ghc %endif -BuildRequires: ghc-rpm-macros-extra +BuildRequires: ghc-rpm-macros-extra >= 2.0 BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel @@ -101,15 +103,19 @@ BuildRequires: ghc-process-devel BuildRequires: ghc-transformers-devel BuildRequires: gmp-devel BuildRequires: libffi-devel +BuildRequires: make # for terminfo BuildRequires: ncurses-devel -# for man and docs BuildRequires: perl-interpreter %if %{with testsuite} BuildRequires: python3 %endif -%if %{with docs} +%if %{with manual} +%if 0%{?fedora} >= 31 BuildRequires: python3-sphinx +%else +BuildRequires: python2-sphinx +%endif %endif %ifarch %{ghc_llvm_archs} BuildRequires: llvm%{llvm_major} @@ -122,10 +128,16 @@ BuildRequires: autoconf, automake %endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} -Requires: ghc-libraries = %{version}-%{release} -%if %{with docs} -Recommends: ghc-doc-cron = %{version}-%{release} -Recommends: ghc-manual = %{version}-%{release} +Requires: ghc-devel = %{version}-%{release} +%if %{with haddock} +Suggests: ghc-doc = %{version}-%{release} +Suggests: ghc-doc-index = %{version}-%{release} +%endif +%if %{with manual} +Suggests: ghc-manual = %{version}-%{release} +%endif +%if %{with ghc_prof} +Suggests: ghc-prof = %{version}-%{release} %endif Recommends: zlib-devel @@ -156,15 +168,8 @@ for the functional language Haskell. Highlights: Summary: GHC compiler and utilities License: BSD Requires: gcc%{?_isa} -Requires: ghc-base-devel%{?_isa} -# for alternatives -Requires(post): %{_sbindir}/update-alternatives -Requires(postun): %{_sbindir}/update-alternatives -# added in f14 -Obsoletes: ghc-doc < 6.12.3-4 -%if %{without docs} -Obsoletes: ghc-doc-cron < %{version}-%{release} -# added in f28 +Requires: ghc-base-devel%{?_isa} = %{base_ver}-%{release} +%if %{without haddock} Obsoletes: ghc-doc-index < %{version}-%{release} %endif %ifarch %{ghc_llvm_archs} @@ -174,28 +179,34 @@ Requires: llvm%{llvm_major} %description compiler The package contains the GHC compiler, tools and utilities. -The ghc libraries are provided by ghc-libraries. +The ghc libraries are provided by ghc-devel. To install all of ghc (including the ghc library), install the main ghc package. -%if %{with docs} -%package doc-cron -Summary: GHC library documentation indexing cronjob +%if %{with haddock} +%package doc +Summary: Haskell library documentation meta package +License: BSD + +%description doc +Installing this package causes ghc-*-doc packages corresponding to ghc-*-devel +packages to be automatically installed too. + + +%package doc-index +Summary: GHC library documentation indexing License: BSD +Obsoletes: ghc-doc-cron < %{version}-%{release} Requires: ghc-compiler = %{version}-%{release} -Requires: crontabs -# added in f28 -Obsoletes: ghc-doc-index < %{version}-%{release} BuildArch: noarch -%description doc-cron -The package provides a cronjob for re-indexing installed library development -documention. +%description doc-index +The package enables re-indexing of installed library documention. %endif -%if %{with docs} +%if %{with manual} %package manual Summary: GHC manual License: BSD @@ -209,35 +220,21 @@ This package provides the User Guide and Haddock manual. # ghclibdir also needs ghc_version_override for bootstrapping %global ghc_version_override %{version} -# EL7 rpm supports fileattrs ghc.attr -%if 0%{?rhel} && 0%{?rhel} < 7 -# needs ghc_version_override for bootstrapping -%global _use_internal_dependency_generator 0 -%global __find_provides /usr/lib/rpm/rpmdeps --provides -%global __find_requires %{_rpmconfigdir}/ghc-deps.sh --requires %{buildroot}%{ghclibdir} -%endif - -%global ghc_pkg_c_deps ghc-compiler = %{ghc_version_override}-%{release} - %global BSDHaskellReport %{quote:BSD and HaskellReport} # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} %ghc_lib_subpackage -d -l BSD Cabal-2.2.0.1 %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.2.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-4.11.1.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %ghc_lib_subpackage -d -l BSD binary-0.8.5.1 %ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 %ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.11.0 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.3.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.1.5 %ghc_lib_subpackage -d -l BSD filepath-1.4.2 -# in ghc not ghc-libraries: -%ghc_lib_subpackage -d -x ghc-%{ghc_version_override} -%ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 -%ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD haskeline-0.7.4.2 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 %ghc_lib_subpackage -d -l BSD mtl-2.2.2 @@ -251,30 +248,42 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD time-1.8.0.2 %ghc_lib_subpackage -d -l BSD transformers-0.5.5.0 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 -%if %{with docs} +%if %{with haddock} %ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1 %endif +# in ghc not ghc-devel: +%ghc_lib_subpackage -d -x ghc-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD -x ghc-boot-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} %endif %global version %{ghc_version_override} -%package libraries +%package devel Summary: GHC development libraries meta package License: BSD and HaskellReport Requires: ghc-compiler = %{version}-%{release} -Obsoletes: ghc-devel < %{version}-%{release} -Provides: ghc-devel = %{version}-%{release} -Obsoletes: ghc-prof < %{version}-%{release} -Provides: ghc-prof = %{version}-%{release} -# since f15 -Obsoletes: ghc-libs < 7.0.1-3 +Obsoletes: ghc-libraries < %{version}-%{release} +Provides: ghc-libraries = %{version}-%{release} %{?ghc_packages_list:Requires: %(echo %{ghc_packages_list} | sed -e "s/\([^ ]*\)-\([^ ]*\)/ghc-\1-devel = \2-%{release},/g")} -%description libraries +%description devel This is a meta-package for all the development library packages in GHC except the ghc library, which is installed by the toplevel ghc metapackage. +%if %{with ghc_prof} +%package prof +Summary: GHC profiling libraries meta package +License: BSD +Requires: ghc-compiler = %{version}-%{release} + +%description prof +Installing this package causes ghc-*-prof packages corresponding to ghc-*-devel +packages to be automatically installed too. +%endif + + %prep %setup -q -n %{name}-%{version} %{?with_testsuite:-b1} @@ -284,9 +293,7 @@ except the ghc library, which is installed by the toplevel ghc metapackage. %patch5 -p1 -b .orig %patch6 -p1 -b .orig -%if 0%{?fedora} || 0%{?rhel} > 6 rm -r libffi-tarballs -%endif %ifarch armv7hl %patch12 -p1 -b .orig @@ -309,7 +316,7 @@ rm -r libffi-tarballs %endif %global gen_contents_index gen_contents_index.orig -%if %{with docs} +%if %{with haddock} if [ ! -f "libraries/%{gen_contents_index}" ]; then echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!" exit 1 @@ -331,15 +338,18 @@ BuildFlavour = quick-llvm BuildFlavour = quick %endif %endif -GhcLibWays = v dyn %{?with_prof:p} -%if %{with docs} +GhcLibWays = v dyn %{?with_ghc_prof:p} +%if %{with haddock} HADDOCK_DOCS = YES -BUILD_MAN = YES +EXTRA_HADDOCK_OPTS += --hyperlinked-source %else HADDOCK_DOCS = NO +%endif +%if %{with manual} +BUILD_MAN = YES +%else BUILD_MAN = NO %endif -EXTRA_HADDOCK_OPTS += --hyperlinked-source BUILD_SPHINX_PDF = NO EOF ## for verbose build output @@ -357,9 +367,7 @@ autoreconf autoconf %endif -# replace later with ghc_set_gcc_flags -export CFLAGS="${CFLAGS:-%optflags}" -export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" +%ghc_set_gcc_flags # for ghc >= 8.2 export CC=%{_bindir}/gcc # * %%configure induces cross-build due to different target/host/build platform names @@ -369,12 +377,10 @@ export CC=%{_bindir}/gcc --libexecdir=%{_libexecdir} --localstatedir=%{_localstatedir} \ --sharedstatedir=%{_sharedstatedir} --mandir=%{_mandir} \ --docdir=%{_docdir}/ghc \ + --with-system-libffi \ %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif -%if 0%{?fedora} || 0%{?rhel} > 6 - --with-system-libffi \ -%endif %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" @@ -386,28 +392,33 @@ make %{?_smp_mflags} make DESTDIR=%{buildroot} install %if %{defined _ghcdynlibdir} -mv %{buildroot}%{ghclibdir}/*/libHS*ghc%{ghc_version}.so %{buildroot}%{_libdir}/ -for i in $(find %{buildroot} -type f -exec sh -c "file {} | grep -q 'dynamically linked'" \; -print); do +mv %{buildroot}%{ghclibdir}/*/libHS*ghc%{ghc_version}.so %{buildroot}%{_ghcdynlibdir}/ +for i in $(find %{buildroot} -type f -executable -exec sh -c "file {} | grep -q 'dynamically linked'" \; -print); do chrpath -d $i done for i in %{buildroot}%{ghclibdir}/package.conf.d/*.conf; do - sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_libdir}!' $i + sed -i -e 's!^dynamic-library-dirs: .*!dynamic-library-dirs: %{_ghcdynlibdir}!' $i done -sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf +sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_ghcdynlibdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %endif +# libraries licenses +rm %{buildroot}%{ghc_html_libraries_dir}/{ghc-prim,integer-gmp}-*/LICENSE +mkdir -p %{buildroot}%{_ghclicensedir} +for i in $(cd %{buildroot}%{ghc_html_libraries_dir}; ls */LICENSE); do + pkg=$(dirname $i | sed -e "s/\\(.*\\)-.*/\\1/") + mkdir %{buildroot}%{_ghclicensedir}/ghc-$pkg + mv %{buildroot}%{ghc_html_libraries_dir}/$i %{buildroot}%{_ghclicensedir}/ghc-$pkg/ +done + for i in %{ghc_packages_list}; do name=$(echo $i | sed -e "s/\(.*\)-.*/\1/") ver=$(echo $i | sed -e "s/.*-\(.*\)/\1/") %ghc_gen_filelists $name $ver -%if 0%{?rhel} && 0%{?rhel} < 7 -echo "%%doc libraries/$name/LICENSE" >> ghc-$name.files -%else -echo "%%license libraries/$name/LICENSE" >> ghc-$name.files -%endif done echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files +echo "%{ghclibdir}/include" >> ghc-base-devel.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} @@ -416,66 +427,34 @@ echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files %ghc_gen_filelists integer-gmp 1.0.2.0 %define merge_filelist()\ -cat ghc-%1.files >> ghc-%2.files\ -cat ghc-%1-devel.files >> ghc-%2-devel.files\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ -%if 0%{?rhel} && 0%{?rhel} < 7\ -echo "%%doc libraries/LICENSE.%1" >> ghc-%2.files\ -%else\ echo "%%license libraries/LICENSE.%1" >> ghc-%2.files\ -%endif +cat ghc-%1.files >> ghc-%2.files\ +for i in devel doc prof; do\ + cat ghc-%1-$i.files >> ghc-%2-$i.files\ +done %merge_filelist integer-gmp base %merge_filelist ghc-prim base # add rts libs -%if %{defined _ghcdynlibdir} -echo "%{ghclibdir}/rts" >> ghc-base-devel.files -%else -echo "%%dir %{ghclibdir}/rts" >> ghc-base.files -ls -d %{buildroot}%{ghclibdir}/rts/lib*.a >> ghc-base-devel.files -%endif -ls %{buildroot}%{?_ghcdynlibdir}%{!?_ghcdynlibdir:%{ghclibdir}/rts}/libHSrts*.so >> ghc-base.files -%if 0%{?rhel} && 0%{?rhel} < 7 -ls %{buildroot}%{ghclibdir}/rts/libffi.so.* >> ghc-base.files -%endif -%if %{defined _ghcdynlibdir} -sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_libdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf -%endif - -ls -d %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %{buildroot}%{ghclibdir}/include >> ghc-base-devel.files -%if 0%{?rhel} && 0%{?rhel} < 7 -ls %{buildroot}%{ghclibdir}/rts/libffi.so >> ghc-base-devel.files -%endif - -sed -i -e "s|^%{buildroot}||g" ghc-base*.files - -# these are handled as alternatives -for i in hsc2hs runhaskell; do - if [ -x %{buildroot}%{_bindir}/$i-ghc ]; then - rm %{buildroot}%{_bindir}/$i - else - mv %{buildroot}%{_bindir}/$i{,-ghc} - fi - touch %{buildroot}%{_bindir}/$i -done - -%if %{with docs} -mkdir -p %{buildroot}%{_sysconfdir}/cron.hourly -install -p --mode=0755 %SOURCE3 %{buildroot}%{_sysconfdir}/cron.hourly/ghc-doc-index -mkdir -p %{buildroot}%{_localstatedir}/lib/ghc -touch %{buildroot}%{_localstatedir}/lib/ghc/pkg-dir.cache{,.new} -install -p --mode=0755 %SOURCE4 %{buildroot}%{_bindir}/ghc-doc-index - +rm -f rts.files +touch rts.files +ls %{buildroot}%{?_ghcdynlibdir}%{!?_ghcdynlibdir:%{ghclibdir}/rts}/libHSrts*-ghc%{ghc_version}.so >> rts.files +find %{buildroot}%{ghclibdir}/rts -type d -fprintf rts-devel.files '%%%%dir %p\n' -o -name 'libHSrts*_p.a' -fprint rts-prof.files -o -fprint rts-devel.files +echo "%{ghclibdir}/package.conf.d/rts.conf" >> rts-devel.files +sed -i -e "s!%{buildroot}!!g" rts.files rts-devel.files rts-prof.files +cat rts.files >> ghc-base.files +cat rts-devel.files >> ghc-base-devel.files +cat rts-prof.files >> ghc-base-prof.files + +%if %{with haddock} # generate initial lib doc index cd libraries sh %{gen_contents_index} --intree --verbose cd .. %endif -# we package the library license files separately -find %{buildroot}%{ghc_html_libraries_dir} -name LICENSE -exec rm '{}' ';' - mkdir -p %{buildroot}%{_mandir}/man1 install -p -m 0644 %{SOURCE5} %{buildroot}%{_mandir}/man1/ghc-pkg.1 install -p -m 0644 %{SOURCE6} %{buildroot}%{_mandir}/man1/haddock.1 @@ -536,30 +515,7 @@ make test %endif -%post compiler -# Alas, GHC, Hugs, and nhc all come with different set of tools in -# addition to a runFOO: -# -# * GHC: hsc2hs -# * Hugs: hsc2hs, cpphs -# * nhc: cpphs -# -# Therefore it is currently not possible to use --slave below to form -# link groups under a single name 'runhaskell'. Either these tools -# should be disentangled from the Haskell implementations, or all -# implementations should have the same set of tools. *sigh* - -update-alternatives --install %{_bindir}/runhaskell runhaskell \ - %{_bindir}/runghc 500 -update-alternatives --install %{_bindir}/hsc2hs hsc2hs \ - %{_bindir}/hsc2hs-ghc 500 - -%preun compiler -if [ "$1" = 0 ]; then - update-alternatives --remove runhaskell %{_bindir}/runghc - update-alternatives --remove hsc2hs %{_bindir}/hsc2hs-ghc -fi - +%if %{defined ghclibdir} %transfiletriggerin compiler -- %{ghclibdir}/package.conf.d %ghc_pkg_recache %end @@ -567,6 +523,19 @@ fi %transfiletriggerpostun compiler -- %{ghclibdir}/package.conf.d %ghc_pkg_recache %end +%endif + + +%if %{with haddock} +%transfiletriggerin doc-index -- %{ghc_html_libraries_dir} +%{ghc_html_libraries_dir}/gen_contents_index +%end + +%transfiletriggerpostun doc-index -- %{ghc_html_libraries_dir} +%{ghc_html_libraries_dir}/gen_contents_index +%end +%endif + %files @@ -581,11 +550,10 @@ fi %{_bindir}/ghci-%{version} %{_bindir}/hp2ps %{_bindir}/hpc -%ghost %{_bindir}/hsc2hs -%{_bindir}/hsc2hs-ghc -%{_bindir}/runghc* -%ghost %{_bindir}/runhaskell -%{_bindir}/runhaskell-ghc +%{_bindir}/hsc2hs +%{_bindir}/runghc +%{_bindir}/runghc-%{ghc_version} +%{_bindir}/runhaskell %dir %{ghclibdir}/bin %{ghclibdir}/bin/ghc %{ghclibdir}/bin/ghc-pkg @@ -593,7 +561,7 @@ fi %{ghclibdir}/bin/hsc2hs %{ghclibdir}/bin/ghc-iserv %{ghclibdir}/bin/ghc-iserv-dyn -%if %{with prof} +%if %{with ghc_prof} %{ghclibdir}/bin/ghc-iserv-prof %endif %{ghclibdir}/bin/runghc @@ -617,16 +585,12 @@ fi %{_mandir}/man1/haddock.1* %{_mandir}/man1/runghc.1* -%if %{with docs} -%{_bindir}/ghc-doc-index +%if %{with haddock} %{_bindir}/haddock %{_bindir}/haddock-ghc-%{version} %{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex -%if %{with docs} -%{_mandir}/man1/ghc.1* -%endif %dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/prologue.txt @@ -640,32 +604,46 @@ fi %ghost %{ghc_html_dir}/libraries/plus.gif %ghost %{ghc_html_dir}/libraries/quick-jump.css %ghost %{ghc_html_dir}/libraries/synopsis.png -%dir %{_localstatedir}/lib/ghc -%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache -%ghost %{_localstatedir}/lib/ghc/pkg-dir.cache.new %endif - -%if %{with docs} -%files doc-cron -%config(noreplace) %{_sysconfdir}/cron.hourly/ghc-doc-index +%if %{with manual} +%{_mandir}/man1/ghc.1* %endif -%files libraries +%files devel +%if %{with haddock} +%files doc -%if %{with docs} +%files doc-index +%endif + +%if %{with manual} %files manual ## needs pandoc #%%{ghc_html_dir}/Cabal -%if %{with docs} +%if %{with haddock} %{ghc_html_dir}/haddock %endif %{ghc_html_dir}/index.html %{ghc_html_dir}/users_guide %endif +%if %{with ghc_prof} +%files prof +%endif + %changelog +* Tue Jul 16 2019 Jens Petersen - 8.4.4-99 +- subpackage library haddock documentation and profiling libraries +- add ghc-doc and ghc-prof metapackages to pull in lib docs and prof libs +- rename ghc-doc-cron with ghc-doc-index using file triggers +- rename ghc-libraries to ghc-devel +- for quickbuild disable debuginfo +- lock ghc-compiler requires ghc-base-devel to ver-rel +- drop alternatives for runhaskell and hsc2hs +- use ghc_set_gcc_flags, with_ghc_prof, and with_haddock + * Thu Jul 25 2019 Fedora Release Engineering - Rebuilt for https://fedoraproject.org/wiki/Fedora_31_Mass_Rebuild From 2d8f07b1a1e3a70c5d164bb0934eb6b9ef05801c Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Jul 2019 16:42:57 +0000 Subject: [PATCH 487/530] lock manual bcond to with_haddock We should probably just use haddock until Hadrian... --- ghc.spec | 15 +++++++++------ 1 file changed, 9 insertions(+), 6 deletions(-) diff --git a/ghc.spec b/ghc.spec index f4eba1a..fc846b9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -11,21 +11,22 @@ %global base_ver 4.11.1.0 # build profiling libraries -# build haddock and manuals -# - earlier combined since disabling haddock seems to cause no manuals built? -# - +# build haddock # perf production build (disable for quick build) %if %{with quickbuild} %undefine with_ghc_prof %undefine with_haddock -%bcond_with manual %bcond_with perf_build %undefine _enable_debug_packages %else -%bcond_without manual %bcond_without perf_build %endif +# locked together since disabling haddock causes no manuals built +# and disabling haddock still created index.html +# https://ghc.haskell.org/trac/ghc/ticket/15190 +%{?with_haddock:%bcond_without manual} + # no longer build testsuite (takes time and not really being used) %bcond_with testsuite @@ -347,8 +348,10 @@ HADDOCK_DOCS = NO %endif %if %{with manual} BUILD_MAN = YES +BUILD_SPHINX_HTML = YES %else BUILD_MAN = NO +BUILD_SPHINX_HTML = NO %endif BUILD_SPHINX_PDF = NO EOF @@ -623,10 +626,10 @@ make test #%%{ghc_html_dir}/Cabal %if %{with haddock} %{ghc_html_dir}/haddock -%endif %{ghc_html_dir}/index.html %{ghc_html_dir}/users_guide %endif +%endif %if %{with ghc_prof} %files prof From 3c34896ffd6b73f6c9f46149ff87f32ee496ac3e Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 17 Jul 2019 16:45:58 +0000 Subject: [PATCH 488/530] haddock: add --hoogle & --quickjump --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index fc846b9..263bd88 100644 --- a/ghc.spec +++ b/ghc.spec @@ -342,7 +342,7 @@ BuildFlavour = quick GhcLibWays = v dyn %{?with_ghc_prof:p} %if %{with haddock} HADDOCK_DOCS = YES -EXTRA_HADDOCK_OPTS += --hyperlinked-source +EXTRA_HADDOCK_OPTS += --hyperlinked-source --hoogle --quickjump %else HADDOCK_DOCS = NO %endif From e55a957f1b259b71255ac1347e152b4841911f21 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 18 Jul 2019 02:45:36 +0000 Subject: [PATCH 489/530] update to ghc-8.6.5 (backported from ghc:8.6) --- .gitignore | 1 + Disable-unboxed-arrays.patch | 12 ++ ...bc8016.patch => ghc-8.6.3-sphinx-1.8.patch | 35 ++---- ghc.spec | 113 +++++++++++------- sources | 2 +- 5 files changed, 98 insertions(+), 65 deletions(-) create mode 100644 Disable-unboxed-arrays.patch rename ghc-sphinx-1.8-4eebc8016.patch => ghc-8.6.3-sphinx-1.8.patch (57%) diff --git a/.gitignore b/.gitignore index 5c04983..33b3d92 100644 --- a/.gitignore +++ b/.gitignore @@ -26,3 +26,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.2.2-src.tar.xz /ghc-8.2.2-testsuite.tar.xz /ghc-8.4.4-src.tar.xz +/ghc-8.6.5-src.tar.xz diff --git a/Disable-unboxed-arrays.patch b/Disable-unboxed-arrays.patch new file mode 100644 index 0000000..17d81c5 --- /dev/null +++ b/Disable-unboxed-arrays.patch @@ -0,0 +1,12 @@ +Index: ghc-8.6.1/libraries/containers/include/containers.h +=================================================================== +--- ghc-8.6.1.orig/libraries/containers/include/containers.h ++++ ghc-8.6.1/libraries/containers/include/containers.h +@@ -35,7 +35,6 @@ + + #ifdef __GLASGOW_HASKELL__ + # define USE_ST_MONAD 1 +-# define USE_UNBOXED_ARRAYS 1 + #endif + + #endif diff --git a/ghc-sphinx-1.8-4eebc8016.patch b/ghc-8.6.3-sphinx-1.8.patch similarity index 57% rename from ghc-sphinx-1.8-4eebc8016.patch rename to ghc-8.6.3-sphinx-1.8.patch index 155be14..2f94fc0 100644 --- a/ghc-sphinx-1.8-4eebc8016.patch +++ b/ghc-8.6.3-sphinx-1.8.patch @@ -1,43 +1,32 @@ -commit 4eebc8016f68719e1ccdf460754a97d1f4d6ef05 -Author: Ben Gamari -Date: Thu Sep 20 08:27:37 2018 -0400 - - users-guide: Fix build with sphinx 1.8 - - It seems that both add_object_type and add_directive_to_domain both register a - directive. Previously sphinx didn't seem to mind this but as of Sphinx 1.8 it - crashes with an exception. - -diff --git a/docs/users_guide/flags.py b/docs/users_guide/flags.py -index a70f7fef1e..284b5e06cc 100644 ---- a/docs/users_guide/flags.py -+++ b/docs/users_guide/flags.py -@@ -48,6 +48,8 @@ from docutils import nodes - from docutils.parsers.rst import Directive, directives +--- ghc-8.6.3/docs/users_guide/flags.py~ 2018-09-21 06:18:23.000000000 +0800 ++++ ghc-8.6.3/docs/users_guide/flags.py 2019-03-05 10:20:38.639782096 +0800 +@@ -49,6 +49,8 @@ + import sphinx from sphinx import addnodes from sphinx.domains.std import GenericObject +from sphinx.domains import ObjType +from sphinx.roles import XRefRole from sphinx.errors import SphinxError + from distutils.version import LooseVersion from utils import build_table_from_list +@@ -603,14 +605,21 @@ + sphinx_version = LooseVersion(sphinx.__version__) + override_arg = {'override': True} if sphinx_version >= LooseVersion('1.8') else {} -@@ -599,14 +601,20 @@ def purge_flags(app, env, docname): - ### Initialization - - def setup(app): + # Yuck: We can't use app.add_object_type since we need to provide the + # Directive instance ourselves. + std_object_types = app.registry.domain_object_types.setdefault('std', {}) - ++ # Add ghc-flag directive, and override the class with our own - app.add_object_type('ghc-flag', 'ghc-flag') - app.add_directive_to_domain('std', 'ghc-flag', Flag) + app.add_directive_to_domain('std', 'ghc-flag', Flag, **override_arg) + app.add_role_to_domain('std', 'ghc-flag', XRefRole()) + std_object_types['ghc-flag'] = ObjType('ghc-flag', 'ghc-flag') # Add extension directive, and override the class with our own - app.add_object_type('extension', 'extension') - app.add_directive_to_domain('std', 'extension', LanguageExtension) + app.add_directive_to_domain('std', 'extension', LanguageExtension, + **override_arg) + app.add_role_to_domain('std', 'extension', XRefRole()) + std_object_types['extension'] = ObjType('ghc-flag', 'ghc-flag') + diff --git a/ghc.spec b/ghc.spec index 263bd88..39338b4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.11.1.0 +%global base_ver 4.12.0.0 # build profiling libraries # build haddock @@ -30,19 +30,19 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.4 needs llvm-5.0 -%global llvm_major 5.0 +# 8.6 needs llvm-6.0 +%global llvm_major 6.0 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc -Version: 8.4.4 +Version: 8.6.5 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 99%{?dist} +Release: 100%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -57,10 +57,8 @@ Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch -# https://github.com/ghc/ghc/pull/143 -Patch5: ghc-configure-fix-sphinx-version-check.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 -Patch6: ghc-sphinx-1.8-4eebc8016.patch +Patch6: ghc-8.6.3-sphinx-1.8.patch # Arch dependent patches @@ -70,19 +68,22 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # for s390x # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch -# https://ghc.haskell.org/trac/ghc/ticket/15853 +# https://gitlab.haskell.org/ghc/ghc/issues/15853 # https://phabricator.haskell.org/D5306 (in 8.8) Patch17: https://gitlab.haskell.org/ghc/ghc/commit/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch -# revert 8.4.4 llvm changes -# https://ghc.haskell.org/trac/ghc/ticket/15780 -Patch16: https://github.com/ghc/ghc/commit/6e361d895dda4600a85e01c72ff219474b5c7190.patch +# bigendian (s390x and ppc64) +# fix haddock-library +# https://gitlab.haskell.org/ghc/ghc/issues/15411 +# https://gitlab.haskell.org/ghc/ghc/issues/16505 +# https://bugzilla.redhat.com/show_bug.cgi?id=1651448 +# https://ghc.haskell.org/trac/ghc/ticket/15914 +Patch18: https://gitlab.haskell.org/ghc/ghc/uploads/5deb133cf910e9e0ca9ad9fe53f7383a/Disable-unboxed-arrays.patch # Debian patches: Patch24: buildpath-abi-stability.patch Patch26: no-missing-haddock-file-warning.patch Patch28: x32-use-native-x86_64-insn.patch -Patch30: fix-build-using-unregisterized-v8.2.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -119,10 +120,12 @@ BuildRequires: python2-sphinx %endif %endif %ifarch %{ghc_llvm_archs} +%if 0%{?fedora} >= 29 BuildRequires: llvm%{llvm_major} +%else +BuildRequires: llvm >= %{llvm_major} +%endif %endif -# patch5 -BuildRequires: autoconf %ifarch armv7hl # patch12 BuildRequires: autoconf, automake @@ -174,7 +177,11 @@ Requires: ghc-base-devel%{?_isa} = %{base_ver}-%{release} Obsoletes: ghc-doc-index < %{version}-%{release} %endif %ifarch %{ghc_llvm_archs} +%if 0%{?fedora} >= 29 Requires: llvm%{llvm_major} +%else +Requires: llvm >= %{llvm_major} +%endif %endif %description compiler @@ -225,37 +232,39 @@ This package provides the User Guide and Haddock manual. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-2.2.0.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.2.0 +%ghc_lib_subpackage -d -l BSD Cabal-2.4.0.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.3.0 %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} -%ghc_lib_subpackage -d -l BSD binary-0.8.5.1 +%ghc_lib_subpackage -d -l BSD binary-0.8.6.0 %ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.5.11.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.3.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.1.5 -%ghc_lib_subpackage -d -l BSD filepath-1.4.2 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.0.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.3.0 +%ghc_lib_subpackage -d -l BSD filepath-1.4.2.1 %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 -%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.2 +%ghc_lib_subpackage -d -l BSD ghc-heap-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.3 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 +%ghc_lib_subpackage -d -l %BSDHaskellReport libiserv-8.6.3 %ghc_lib_subpackage -d -l BSD mtl-2.2.2 %ghc_lib_subpackage -d -l BSD parsec-3.1.13.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.3.0 -%ghc_lib_subpackage -d -l BSD stm-2.4.5.1 -%ghc_lib_subpackage -d -l BSD template-haskell-2.13.0.0 -%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.5.0 +%ghc_lib_subpackage -d -l BSD stm-2.5.0.0 +%ghc_lib_subpackage -d -l BSD template-haskell-2.14.0.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.2 %ghc_lib_subpackage -d -l BSD text-1.2.3.1 %ghc_lib_subpackage -d -l BSD time-1.8.0.2 -%ghc_lib_subpackage -d -l BSD transformers-0.5.5.0 +%ghc_lib_subpackage -d -l BSD transformers-0.5.6.2 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{with haddock} %ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1 %endif # in ghc not ghc-devel: %ghc_lib_subpackage -d -x ghc-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD -x ghc-boot-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} +%ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} +%ghc_lib_subpackage -d -x -l BSD ghci-%{ghc_version_override} %endif %global version %{ghc_version_override} @@ -291,7 +300,6 @@ packages to be automatically installed too. %patch1 -p1 -b .orig %patch2 -p1 -b .orig -%patch5 -p1 -b .orig %patch6 -p1 -b .orig rm -r libffi-tarballs @@ -300,21 +308,19 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif -%ifarch s390x +%ifarch %{ghc_unregisterized_arches} %patch15 -p1 -b .orig %patch17 -p1 -b .orig %endif -%ifarch armv7hl aarch64 -%patch16 -p1 -b .orig -R +# bigendian +%ifarch ppc64 s390x +%patch18 -p1 -b .orig %endif %patch24 -p1 -b .orig %patch26 -p1 -b .orig %patch28 -p1 -b .orig -%ifarch s390x -%patch30 -p1 -b .orig -%endif %global gen_contents_index gen_contents_index.orig %if %{with haddock} @@ -365,14 +371,27 @@ EOF # for patch12 %ifarch armv7hl autoreconf -%else -# for patch5 -autoconf %endif +%if 0%{?fedora} > 28 %ghc_set_gcc_flags +%else +export CFLAGS="${CFLAGS:-%optflags}" +export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" +%endif # for ghc >= 8.2 export CC=%{_bindir}/gcc + +# remove after Fedora default moves to 8.6 +%ifarch %{ghc_unregisterized_arches} +cat > ghc-unregisterised-wrapper << EOF +#!/usr/bin/sh +exec /usr/bin/ghc -optc-I%{_libdir}/ghc-$(ghc --numeric-version)/include \${1+"\$@"} +EOF +chmod a+x ghc-unregisterised-wrapper +ln -s /usr/bin/ghc-pkg ghc-pkg-unregisterised-wrapper +%endif + # * %%configure induces cross-build due to different target/host/build platform names ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ @@ -383,6 +402,7 @@ export CC=%{_bindir}/gcc --with-system-libffi \ %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ + --with-ghc=$PWD/ghc-unregisterised-wrapper \ %endif %{nil} @@ -426,7 +446,7 @@ echo "%{ghclibdir}/include" >> ghc-base-devel.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.5.2.0 +%ghc_gen_filelists ghc-prim 0.5.3 %ghc_gen_filelists integer-gmp 1.0.2.0 %define merge_filelist()\ @@ -575,6 +595,7 @@ make test %{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt %{ghclibdir}/ghci-usage.txt +%{ghclibdir}/llvm-passes %{ghclibdir}/llvm-targets %dir %{ghclibdir}/package.conf.d %ghost %{ghclibdir}/package.conf.d/package.cache @@ -637,6 +658,16 @@ make test %changelog +* Wed Jul 17 2019 Jens Petersen - 8.6.5-100 +- update to GHC 8.6.5 (backport ghc:8.6 module stream) +- https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.1-notes.html +- https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.2-notes.html +- https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.3-notes.html +- https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.4-notes.html +- https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.5-notes.html +- enable s390x with unregisterized workaround for 8.4 (#1648537) +- also re-enable ppc64 with bigendian patch for containers (#1651448) + * Tue Jul 16 2019 Jens Petersen - 8.4.4-99 - subpackage library haddock documentation and profiling libraries - add ghc-doc and ghc-prof metapackages to pull in lib docs and prof libs diff --git a/sources b/sources index a6f24f6..3790399 100644 --- a/sources +++ b/sources @@ -1 +1 @@ -SHA512 (ghc-8.4.4-src.tar.xz) = 685e102eee8cf8b6a377afd7871998c8c368a5da288469367e3fb804aa6109e6f59be5945b8cd3d1e36c851190ea9a7f74c576528589589313d237b721d86da5 +SHA512 (ghc-8.6.5-src.tar.xz) = c08a7480200cb99e1ffbe4ce7669f552b1054054966f7e7efcbc5f98af8032e1249fa391c4fc4c7d62cc8e0be5d17fa05845177f3cea3dbcf86e6c92d40fc0f9 From bbb20669df67f43a50e3d4cabe2883beaeab3158 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 19 Jul 2019 03:02:09 +0000 Subject: [PATCH 490/530] fix initgroups issue in process library https://github.com/haskell/process/pull/148 --- ...12fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch | 92 +++++++++++++++++++ ...41b3622e2e578d928f7513941aac9d873279.patch | 24 +++++ ghc.spec | 12 +++ 3 files changed, 128 insertions(+) create mode 100644 3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch create mode 100644 73ea41b3622e2e578d928f7513941aac9d873279.patch diff --git a/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch b/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch new file mode 100644 index 0000000..98a7925 --- /dev/null +++ b/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch @@ -0,0 +1,92 @@ +From 3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b Mon Sep 17 00:00:00 2001 +From: Ben Gamari +Date: Mon, 1 Jul 2019 11:03:33 -0400 +Subject: [PATCH] Call initgroups before setuid + +Previously we would fail to call initgroups before setuid'ing. This +meant that our groups we not be reset to reflect those our new user +belongs to. Fix this. +--- + cbits/runProcess.c | 32 +++++++++++++++++++++++++++++--- + include/runProcess.h | 4 ++++ + 2 files changed, 33 insertions(+), 3 deletions(-) + +diff --git a/cbits/runProcess.c b/cbits/runProcess.c +index 10794bc..84d5fd4 100644 +--- a/cbits/runProcess.c ++++ b/cbits/runProcess.c +@@ -33,6 +33,10 @@ static long max_fd = 0; + extern void blockUserSignals(void); + extern void unblockUserSignals(void); + ++// These are arbitrarily chosen -- JP ++#define forkSetgidFailed 124 ++#define forkSetuidFailed 125 ++ + // See #1593. The convention for the exit code when + // exec() fails seems to be 127 (gleened from C's + // system()), but there's no equivalent convention for +@@ -40,9 +44,8 @@ extern void unblockUserSignals(void); + #define forkChdirFailed 126 + #define forkExecFailed 127 + +-// These are arbitrarily chosen -- JP +-#define forkSetgidFailed 124 +-#define forkSetuidFailed 125 ++#define forkGetpwuidFailed 128 ++#define forkInitgroupsFailed 129 + + __attribute__((__noreturn__)) + static void childFailed(int pipe, int failCode) { +@@ -182,6 +185,23 @@ runInteractiveProcess (char *const args[], + } + + if ( childUser) { ++ // Using setuid properly first requires that we initgroups. ++ // However, to do this we must know the username of the user we are ++ // switching to. ++ struct passwd pw; ++ struct passwd *res = NULL; ++ int buf_len = sysconf(_SC_GETPW_R_SIZE_MAX); ++ char *buf = malloc(buf_len); ++ gid_t suppl_gid = childGroup ? *childGroup : getgid(); ++ if ( getpwuid_r(*childUser, &pw, buf, buf_len, &res) != 0) { ++ childFailed(forkCommunicationFds[1], forkGetpwuidFailed); ++ } ++ if ( res == NULL ) { ++ childFailed(forkCommunicationFds[1], forkGetpwuidFailed); ++ } ++ if ( initgroups(res->pw_name, suppl_gid) != 0) { ++ childFailed(forkCommunicationFds[1], forkInitgroupsFailed); ++ } + if ( setuid( *childUser) != 0) { + // ERROR + childFailed(forkCommunicationFds[1], forkSetuidFailed); +@@ -330,6 +350,12 @@ runInteractiveProcess (char *const args[], + case forkSetuidFailed: + *failed_doing = "runInteractiveProcess: setuid"; + break; ++ case forkGetpwuidFailed: ++ *failed_doing = "runInteractiveProcess: getpwuid"; ++ break; ++ case forkInitgroupsFailed: ++ *failed_doing = "runInteractiveProcess: initgroups"; ++ break; + default: + *failed_doing = "runInteractiveProcess: unknown"; + break; +diff --git a/include/runProcess.h b/include/runProcess.h +index 3807389..dff3905 100644 +--- a/include/runProcess.h ++++ b/include/runProcess.h +@@ -21,6 +21,10 @@ + + #include + #include ++#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32)) ++#include ++#include ++#endif + + #ifdef HAVE_FCNTL_H + #include diff --git a/73ea41b3622e2e578d928f7513941aac9d873279.patch b/73ea41b3622e2e578d928f7513941aac9d873279.patch new file mode 100644 index 0000000..5b8d646 --- /dev/null +++ b/73ea41b3622e2e578d928f7513941aac9d873279.patch @@ -0,0 +1,24 @@ +From 73ea41b3622e2e578d928f7513941aac9d873279 Mon Sep 17 00:00:00 2001 +From: Ben Gamari +Date: Mon, 1 Jul 2019 11:02:45 -0400 +Subject: [PATCH] Fix incorrect case fallthrough + +The error message lookup logic would fallthrough from the +forkSetuidFailed case into the default case, meaning that the error +message of the former would never be returned. +--- + cbits/runProcess.c | 1 + + 1 file changed, 1 insertion(+) + +diff --git a/cbits/runProcess.c b/cbits/runProcess.c +index c621158..10794bc 100644 +--- a/cbits/runProcess.c ++++ b/cbits/runProcess.c +@@ -329,6 +329,7 @@ runInteractiveProcess (char *const args[], + break; + case forkSetuidFailed: + *failed_doing = "runInteractiveProcess: setuid"; ++ break; + default: + *failed_doing = "runInteractiveProcess: unknown"; + break; diff --git a/ghc.spec b/ghc.spec index 39338b4..07942ff 100644 --- a/ghc.spec +++ b/ghc.spec @@ -60,6 +60,10 @@ Patch2: ghc-Cabal-install-PATH-warning.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch +# https://github.com/haskell/process/pull/148 +Patch10: https://github.com/haskell/process/commit/73ea41b3622e2e578d928f7513941aac9d873279.patch +Patch11: https://github.com/haskell/process/commit/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch + # Arch dependent patches # arm @@ -304,6 +308,12 @@ packages to be automatically installed too. rm -r libffi-tarballs +( +cd libraries/process +%patch10 -p1 -b .orig10 +%patch11 -p1 -b .orig11 +) + %ifarch armv7hl %patch12 -p1 -b .orig %endif @@ -665,6 +675,8 @@ make test - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.3-notes.html - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.4-notes.html - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.5-notes.html +- fix process library initgroups issue + (https://github.com/haskell/process/pull/148) - enable s390x with unregisterized workaround for 8.4 (#1648537) - also re-enable ppc64 with bigendian patch for containers (#1651448) From 289a7ed191b62a74fb187fb71e17bed9d072ca45 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 27 Jul 2019 12:05:55 +0000 Subject: [PATCH 491/530] add some patches from Debian (thanks!) https://salsa.debian.org/haskell-team/DHG_packages/tree/master/p/ghc/debian/patches - rename 35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch -> PprC-Add-support-for-adjacent-floats.patch - add_-latomic_to_ghc-prim.patch - e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch (rts osReserveHeapMemory block alignment) --- ...PprC-Add-support-for-adjacent-floats.patch | 0 add_-latomic_to_ghc-prim.patch | 54 ++++++++++++++++ ...aaf6918bb2b497b83618dc4c270a0d231a1c.patch | 63 +++++++++++++++++++ ghc.spec | 13 +++- 4 files changed, 128 insertions(+), 2 deletions(-) rename 35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch => PprC-Add-support-for-adjacent-floats.patch (100%) create mode 100644 add_-latomic_to_ghc-prim.patch create mode 100644 e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch diff --git a/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch b/PprC-Add-support-for-adjacent-floats.patch similarity index 100% rename from 35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch rename to PprC-Add-support-for-adjacent-floats.patch diff --git a/add_-latomic_to_ghc-prim.patch b/add_-latomic_to_ghc-prim.patch new file mode 100644 index 0000000..71e4ddb --- /dev/null +++ b/add_-latomic_to_ghc-prim.patch @@ -0,0 +1,54 @@ +commit ce3897ffd6e7c8b8f36b8e920168bac8c7f836ae +Author: Ilias Tsitsimpis +Date: Tue Sep 18 17:45:17 2018 +0200 + + Fix check whether GCC supports __atomic_ builtins + + Summary: + C11 atomics are never used because: + + * The program used for checking whether GCC supports + __atomic_ builtins fails with the following error: + + ``` + error: size mismatch in argument 2 of `__atomic_load` + int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; } + ``` + + * There is a typo when checking if CONF_GCC_SUPPORTS__ATOMICS equals YES, + resulting in PRIM_CFLAGS and PRIM_EXTRA_LIBRARIES never being set. + + Reviewers: bgamari + + Reviewed By: bgamari + + Subscribers: rwbarton, erikd, carter + + Differential Revision: https://phabricator.haskell.org/D5154 + +Index: b/libraries/ghc-prim/aclocal.m4 +=================================================================== +--- a/libraries/ghc-prim/aclocal.m4 ++++ b/libraries/ghc-prim/aclocal.m4 +@@ -5,7 +5,7 @@ AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], + [ + AC_REQUIRE([AC_PROG_CC]) + AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) +- echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c ++ echo 'int test(int *x) { int y; __atomic_load(x, &y, __ATOMIC_SEQ_CST); return y; }' > conftest.c + if $CC -c conftest.c > /dev/null 2>&1; then + CONF_GCC_SUPPORTS__ATOMICS=YES + AC_MSG_RESULT([yes]) +Index: b/libraries/ghc-prim/configure.ac +=================================================================== +--- a/libraries/ghc-prim/configure.ac ++++ b/libraries/ghc-prim/configure.ac +@@ -8,7 +8,7 @@ dnl unregisterised, Sparc, and PPC ba + FP_GCC_SUPPORTS__ATOMICS + AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) + +-if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES ++if test "$CONF_GCC_SUPPORTS__ATOMICS" = "YES" + then PRIM_CFLAGS=-DHAVE_C11_ATOMICS + PRIM_EXTRA_LIBRARIES=atomic + fi diff --git a/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch b/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch new file mode 100644 index 0000000..8824289 --- /dev/null +++ b/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch @@ -0,0 +1,63 @@ +From: Sergei Trofimovich +Date: Wed, 18 Jul 2018 22:36:58 +0000 (+0100) +Subject: fix osReserveHeapMemory block alignment +X-Git-Url: https://git.haskell.org/ghc.git/commitdiff_plain/e175aaf6918bb2b497b83618dc4c270a0d231a1c + +fix osReserveHeapMemory block alignment + +Before the change osReserveHeapMemory() attempted +to allocate chunks of memory via osTryReserveHeapMemory() +not multiple of MBLOCK_SIZE in the following fallback code: + +``` + if (at == NULL) { + *len -= *len / 8; +``` + +and caused assertion failure: + +``` +$ make fulltest TEST=T11607 WAY=threaded1 +T11607: internal error: ASSERTION FAILED: file rts/posix/OSMem.c, line 457 + (GHC version 8.7.20180716 for riscv64_unknown_linux) + +``` + +The change applies alignment mask before each MBLOCK allocation attempt +and fixes WAY=threaded1 test failures on qemu-riscv64. + +Signed-off-by: Sergei Trofimovich + +Test Plan: run 'make fulltest WAY=threaded1' + +Reviewers: simonmar, bgamari, erikd + +Reviewed By: simonmar + +Subscribers: rwbarton, thomie, carter + +Differential Revision: https://phabricator.haskell.org/D4982 +--- + +Index: b/rts/posix/OSMem.c +=================================================================== +--- a/rts/posix/OSMem.c ++++ b/rts/posix/OSMem.c +@@ -476,6 +476,8 @@ osTryReserveHeapMemory (W_ len, void *hi + void *base, *top; + void *start, *end; + ++ ASSERT((len & ~MBLOCK_MASK) == len); ++ + /* We try to allocate len + MBLOCK_SIZE, + because we need memory which is MBLOCK_SIZE aligned, + and then we discard what we don't need */ +@@ -552,6 +554,8 @@ void *osReserveHeapMemory(void *startAdd + + attempt = 0; + while (1) { ++ *len &= ~MBLOCK_MASK; ++ + if (*len < MBLOCK_SIZE) { + // Give up if the system won't even give us 16 blocks worth of heap + barf("osReserveHeapMemory: Failed to allocate heap storage"); diff --git a/ghc.spec b/ghc.spec index 07942ff..a2808bd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -69,12 +69,14 @@ Patch11: https://github.com/haskell/process/commit/3e0812fe9d3f4712638a1c4c49bf2 # arm Patch12: ghc-armv7-VFPv3D16--NEON.patch -# for s390x +# for unregisterized (s390x) # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch # https://gitlab.haskell.org/ghc/ghc/issues/15853 # https://phabricator.haskell.org/D5306 (in 8.8) -Patch17: https://gitlab.haskell.org/ghc/ghc/commit/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch +# https://gitlab.haskell.org/ghc/ghc/commit/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch +# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/PprC-Add-support-for-adjacent-floats +Patch17: PprC-Add-support-for-adjacent-floats.patch # bigendian (s390x and ppc64) # fix haddock-library @@ -88,6 +90,10 @@ Patch18: https://gitlab.haskell.org/ghc/ghc/uploads/5deb133cf910e9e0ca9ad9fe53f7 Patch24: buildpath-abi-stability.patch Patch26: no-missing-haddock-file-warning.patch Patch28: x32-use-native-x86_64-insn.patch +# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/add_-latomic_to_ghc-prim +Patch30: add_-latomic_to_ghc-prim.patch +# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch +Patch32: https://salsa.debian.org/haskell-team/DHG_packages/raw/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -328,9 +334,12 @@ cd libraries/process %patch18 -p1 -b .orig %endif +# debian %patch24 -p1 -b .orig %patch26 -p1 -b .orig %patch28 -p1 -b .orig +%patch30 -p1 -b .orig +%patch32 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{with haddock} From 5540152920468de33c0ad74ca7038a4843255b7f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 27 Jul 2019 12:08:22 +0000 Subject: [PATCH 492/530] use Debian fix-build-using-unregisterized-v8.4.patch https://gitlab.haskell.org/ghc/ghc/issues/15913 - remove ghc wrapper script hack! --- fix-build-using-unregisterized-v8.4.patch | 58 +++++++++++++++++++++++ ghc.spec | 16 ++----- 2 files changed, 63 insertions(+), 11 deletions(-) create mode 100644 fix-build-using-unregisterized-v8.4.patch diff --git a/fix-build-using-unregisterized-v8.4.patch b/fix-build-using-unregisterized-v8.4.patch new file mode 100644 index 0000000..c524733 --- /dev/null +++ b/fix-build-using-unregisterized-v8.4.patch @@ -0,0 +1,58 @@ +Description: Allow unregisterised ghc-8.4 to build newer GHC + Commit 4075656e8bb introduced a regression stopping existing unregisteristed + compilers from being able to compile newer versions of GHC. The problem is + that the bootstrap compiler uses the newer `rts/storage/ClosureTypes.h` file + where some defines have been renamed, resulting in the following error: +. + error: ‘stg_MUT_ARR_PTRS_FROZEN0_info’ undeclared (first use in this function); did you mean ‘stg_MUT_ARR_PTRS_FROZEN_DIRTY_info’? +. + For more information, see https://gitlab.haskell.org/ghc/ghc/issues/15913. +. + This patch can be removed, once ghc-8.4 is no longer the bootstrap compiler. +Author: Ilias Tsitsimpis +Bug: https://gitlab.haskell.org/ghc/ghc/issues/15913 +Bug-Debian: https://bugs.debian.org/932941 + +Index: b/includes/rts/storage/ClosureTypes.h +=================================================================== +--- a/includes/rts/storage/ClosureTypes.h ++++ b/includes/rts/storage/ClosureTypes.h +@@ -82,5 +82,11 @@ + #define SMALL_MUT_ARR_PTRS_DIRTY 60 + #define SMALL_MUT_ARR_PTRS_FROZEN_DIRTY 61 + #define SMALL_MUT_ARR_PTRS_FROZEN_CLEAN 62 ++#if __GLASGOW_HASKELL__ < 806 ++#define SMALL_MUT_ARR_PTRS_FROZEN0 SMALL_MUT_ARR_PTRS_FROZEN_DIRTY ++#define SMALL_MUT_ARR_PTRS_FROZEN SMALL_MUT_ARR_PTRS_FROZEN_CLEAN ++#define MUT_ARR_PTRS_FROZEN0 MUT_ARR_PTRS_FROZEN_DIRTY ++#define MUT_ARR_PTRS_FROZEN MUT_ARR_PTRS_FROZEN_CLEAN ++#endif + #define COMPACT_NFDATA 63 + #define N_CLOSURE_TYPES 64 +Index: b/includes/stg/MiscClosures.h +=================================================================== +--- a/includes/stg/MiscClosures.h ++++ b/includes/stg/MiscClosures.h +@@ -116,12 +116,22 @@ RTS_ENTRY(stg_ARR_WORDS); + RTS_ENTRY(stg_MUT_ARR_WORDS); + RTS_ENTRY(stg_MUT_ARR_PTRS_CLEAN); + RTS_ENTRY(stg_MUT_ARR_PTRS_DIRTY); ++#if __GLASGOW_HASKELL__ < 806 ++RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN); ++RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN0); ++#else + RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN_CLEAN); + RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN_DIRTY); ++#endif + RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_CLEAN); + RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_DIRTY); ++#if __GLASGOW_HASKELL__ < 806 ++RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN); ++RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN0); ++#else + RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN_CLEAN); + RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN_DIRTY); ++#endif + RTS_ENTRY(stg_MUT_VAR_CLEAN); + RTS_ENTRY(stg_MUT_VAR_DIRTY); + RTS_ENTRY(stg_END_TSO_QUEUE); diff --git a/ghc.spec b/ghc.spec index a2808bd..57ffcae 100644 --- a/ghc.spec +++ b/ghc.spec @@ -94,6 +94,10 @@ Patch28: x32-use-native-x86_64-insn.patch Patch30: add_-latomic_to_ghc-prim.patch # https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch Patch32: https://salsa.debian.org/haskell-team/DHG_packages/raw/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch +# https://gitlab.haskell.org/ghc/ghc/issues/15913 +# remove after Fedora default moves to 8.6 +# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/fix-build-using-unregisterized-v8.4 +Patch34: fix-build-using-unregisterized-v8.4.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -327,6 +331,7 @@ cd libraries/process %ifarch %{ghc_unregisterized_arches} %patch15 -p1 -b .orig %patch17 -p1 -b .orig +%patch34 -p1 -b .orig %endif # bigendian @@ -401,16 +406,6 @@ export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" # for ghc >= 8.2 export CC=%{_bindir}/gcc -# remove after Fedora default moves to 8.6 -%ifarch %{ghc_unregisterized_arches} -cat > ghc-unregisterised-wrapper << EOF -#!/usr/bin/sh -exec /usr/bin/ghc -optc-I%{_libdir}/ghc-$(ghc --numeric-version)/include \${1+"\$@"} -EOF -chmod a+x ghc-unregisterised-wrapper -ln -s /usr/bin/ghc-pkg ghc-pkg-unregisterised-wrapper -%endif - # * %%configure induces cross-build due to different target/host/build platform names ./configure --prefix=%{_prefix} --exec-prefix=%{_exec_prefix} \ --bindir=%{_bindir} --sbindir=%{_sbindir} --sysconfdir=%{_sysconfdir} \ @@ -421,7 +416,6 @@ ln -s /usr/bin/ghc-pkg ghc-pkg-unregisterised-wrapper --with-system-libffi \ %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ - --with-ghc=$PWD/ghc-unregisterised-wrapper \ %endif %{nil} From 42966dc862670187d4a73cf26824494beb30b015 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 27 Jul 2019 12:26:41 +0000 Subject: [PATCH 493/530] update changelog with latest patches --- ghc.spec | 9 +++++++-- 1 file changed, 7 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 57ffcae..7728f42 100644 --- a/ghc.spec +++ b/ghc.spec @@ -680,8 +680,13 @@ make test - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.5-notes.html - fix process library initgroups issue (https://github.com/haskell/process/pull/148) -- enable s390x with unregisterized workaround for 8.4 (#1648537) -- also re-enable ppc64 with bigendian patch for containers (#1651448) +- add fix-build-using-unregisterized-v8.4.patch for s390x (#1648537) + https://gitlab.haskell.org/ghc/ghc/issues/15913 +- add bigendian patch for containers (#1651448) + https://gitlab.haskell.org/ghc/ghc/issues/15411 +- Debian patches: + - add_-latomic_to_ghc-prim.patch, + - rts osReserveHeapMemory block alignment * Tue Jul 16 2019 Jens Petersen - 8.4.4-99 - subpackage library haddock documentation and profiling libraries From a5e107a6171356233d6918dc9c458292e963ad36 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 31 Jul 2019 10:17:47 +0000 Subject: [PATCH 494/530] reset changelog date --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 7728f42..1cecd77 100644 --- a/ghc.spec +++ b/ghc.spec @@ -671,7 +671,7 @@ make test %changelog -* Wed Jul 17 2019 Jens Petersen - 8.6.5-100 +* Wed Jul 31 2019 Jens Petersen - 8.6.5-100 - update to GHC 8.6.5 (backport ghc:8.6 module stream) - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.1-notes.html - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.2-notes.html From 4df46f41cafbc3d5b47d0bf7aa7bd962d18a45ff Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 31 Jul 2019 10:21:42 +0000 Subject: [PATCH 495/530] order previous changelog too --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 1cecd77..bba8749 100644 --- a/ghc.spec +++ b/ghc.spec @@ -688,7 +688,7 @@ make test - add_-latomic_to_ghc-prim.patch, - rts osReserveHeapMemory block alignment -* Tue Jul 16 2019 Jens Petersen - 8.4.4-99 +* Tue Jul 30 2019 Jens Petersen - 8.4.4-99 - subpackage library haddock documentation and profiling libraries - add ghc-doc and ghc-prof metapackages to pull in lib docs and prof libs - rename ghc-doc-cron with ghc-doc-index using file triggers From e29d53ee13b9064572a989cf1e40e9b67ad1b32a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 31 Jul 2019 16:54:40 +0000 Subject: [PATCH 496/530] try %bcond haddock for full build since macros.ghc-os only available in full builtroot --- ghc.spec | 1 + 1 file changed, 1 insertion(+) diff --git a/ghc.spec b/ghc.spec index bba8749..9fc1474 100644 --- a/ghc.spec +++ b/ghc.spec @@ -19,6 +19,7 @@ %bcond_with perf_build %undefine _enable_debug_packages %else +%bcond_without haddock %bcond_without perf_build %endif From 0d81ce7231d1a75a0dd7eace33ba365fcdcd436b Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Tue, 28 Jan 2020 20:07:50 +0000 Subject: [PATCH 497/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_32_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 9fc1474..2e6a30e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -43,7 +43,7 @@ Version: 8.6.5 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 100%{?dist} +Release: 101%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -672,6 +672,9 @@ make test %changelog +* Tue Jan 28 2020 Fedora Release Engineering - 8.6.5-101 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_32_Mass_Rebuild + * Wed Jul 31 2019 Jens Petersen - 8.6.5-100 - update to GHC 8.6.5 (backport ghc:8.6 module stream) - https://downloads.haskell.org/~ghc/8.6.5/docs/html/users_guide/8.6.1-notes.html From ba78a30353049aa1f3b211b3cd017ec6ce56612a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 10 Feb 2020 19:30:18 +0800 Subject: [PATCH 498/530] rebuild against ghc-rpm-macros fixed for subpackage prof deps testcase: ghc-prof(...) was missing from generated Requires --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index 2e6a30e..dd93d7d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -43,7 +43,7 @@ Version: 8.6.5 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 101%{?dist} +Release: 102%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -110,7 +110,7 @@ BuildRequires: ghc-compiler %if %{with abicheck} BuildRequires: ghc %endif -BuildRequires: ghc-rpm-macros-extra >= 2.0 +BuildRequires: ghc-rpm-macros-extra >= 2.0.6 BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel @@ -672,6 +672,9 @@ make test %changelog +* Mon Feb 10 2020 Jens Petersen - 8.6.5-102 +- rebuild against ghc-rpm-macros fixed for subpackage prof deps + * Tue Jan 28 2020 Fedora Release Engineering - 8.6.5-101 - Rebuilt for https://fedoraproject.org/wiki/Fedora_32_Mass_Rebuild From 933e1cf71ace8d7821628a3420235b23aac8ab58 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 10 Mar 2020 20:07:34 +0800 Subject: [PATCH 499/530] add bcond for dwarf-unwind debuginfo --- ghc.spec | 16 ++++++++++++++++ 1 file changed, 16 insertions(+) diff --git a/ghc.spec b/ghc.spec index dd93d7d..15de414 100644 --- a/ghc.spec +++ b/ghc.spec @@ -23,6 +23,11 @@ %bcond_without perf_build %endif +# to enable dwarf-unwind debug (only on intel archs) +%ifarch x86_64 i686 +%bcond_with dwarf_unwind +%endif + # locked together since disabling haddock causes no manuals built # and disabling haddock still created index.html # https://ghc.haskell.org/trac/ghc/ticket/15190 @@ -141,6 +146,9 @@ BuildRequires: llvm%{llvm_major} BuildRequires: llvm >= %{llvm_major} %endif %endif +%if %{with dwarf_unwind} +BuildRequires: elfutils-devel +%endif %ifarch armv7hl # patch12 BuildRequires: autoconf, automake @@ -371,6 +379,10 @@ BuildFlavour = quick %endif %endif GhcLibWays = v dyn %{?with_ghc_prof:p} +%if %{with dwarf_unwind} +GhcLibHcOpts += -g3 +GhcRtsHcOpts += -g3 +%endif %if %{with haddock} HADDOCK_DOCS = YES EXTRA_HADDOCK_OPTS += --hyperlinked-source --hoogle --quickjump @@ -418,6 +430,7 @@ export CC=%{_bindir}/gcc %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif + %{?with_dwarf_unwind:--enable-dwarf-unwind} \ %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" @@ -672,6 +685,9 @@ make test %changelog +* Tue Mar 10 2020 Jens Petersen +- add bcond for dwarf-unwind debuginfo + * Mon Feb 10 2020 Jens Petersen - 8.6.5-102 - rebuild against ghc-rpm-macros fixed for subpackage prof deps From 3219874865623919f0eeb18144c8bb81620f1a17 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 11 Mar 2020 00:57:22 +0800 Subject: [PATCH 500/530] rename dwarf_unwind to dwarf and use dwarf flavour --- ghc.spec | 24 ++++++++++-------------- 1 file changed, 10 insertions(+), 14 deletions(-) diff --git a/ghc.spec b/ghc.spec index 15de414..91e49f1 100644 --- a/ghc.spec +++ b/ghc.spec @@ -23,9 +23,10 @@ %bcond_without perf_build %endif -# to enable dwarf-unwind debug (only on intel archs) +# to enable dwarf info (only on intel archs): overrides perf +# default is off: bcond_with %ifarch x86_64 i686 -%bcond_with dwarf_unwind +%bcond_with dwarf %endif # locked together since disabling haddock causes no manuals built @@ -146,7 +147,7 @@ BuildRequires: llvm%{llvm_major} BuildRequires: llvm >= %{llvm_major} %endif %endif -%if %{with dwarf_unwind} +%if %{with dwarf} BuildRequires: elfutils-devel %endif %ifarch armv7hl @@ -369,8 +370,12 @@ cat > mk/build.mk << EOF %ifarch %{ghc_llvm_archs} BuildFlavour = perf-llvm %else +%if %{with dwarf} +BuildFlavour = dwarf +%else BuildFlavour = perf %endif +%endif %else %ifarch %{ghc_llvm_archs} BuildFlavour = quick-llvm @@ -379,10 +384,6 @@ BuildFlavour = quick %endif %endif GhcLibWays = v dyn %{?with_ghc_prof:p} -%if %{with dwarf_unwind} -GhcLibHcOpts += -g3 -GhcRtsHcOpts += -g3 -%endif %if %{with haddock} HADDOCK_DOCS = YES EXTRA_HADDOCK_OPTS += --hyperlinked-source --hoogle --quickjump @@ -398,11 +399,6 @@ BUILD_SPHINX_HTML = NO %endif BUILD_SPHINX_PDF = NO EOF -## for verbose build output -#GhcStage1HcOpts=-v4 -## enable RTS debugging: -## (http://ghc.haskell.org/trac/ghc/wiki/Debugging/RuntimeSystem) -#EXTRA_HC_OPTS=-debug %build # for patch12 @@ -430,7 +426,7 @@ export CC=%{_bindir}/gcc %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif - %{?with_dwarf_unwind:--enable-dwarf-unwind} \ + %{?with_dwarf:--enable-dwarf-unwind} \ %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" @@ -686,7 +682,7 @@ make test %changelog * Tue Mar 10 2020 Jens Petersen -- add bcond for dwarf-unwind debuginfo +- add bcond for dwarf info * Mon Feb 10 2020 Jens Petersen - 8.6.5-102 - rebuild against ghc-rpm-macros fixed for subpackage prof deps From c99aae1e558bc3c8b44c3dc3414d5bce6498bc73 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 9 Apr 2020 18:30:23 +0800 Subject: [PATCH 501/530] fix gen_contents_index also when no docs (#1813548) - cronjob used to switch to /usr/share/doc/ghc/html/libraries - since docs now subpackaged, need to check for no docs - we could also recommend ghc-base-doc --- ghc-gen_contents_index-nodocs.patch | 11 +++++++++++ ghc.spec | 13 ++++++++----- 2 files changed, 19 insertions(+), 5 deletions(-) create mode 100644 ghc-gen_contents_index-nodocs.patch diff --git a/ghc-gen_contents_index-nodocs.patch b/ghc-gen_contents_index-nodocs.patch new file mode 100644 index 0000000..bb7f9a6 --- /dev/null +++ b/ghc-gen_contents_index-nodocs.patch @@ -0,0 +1,11 @@ +--- ghc-8.6.5/libraries/gen_contents_index~ 2020-02-24 15:02:26.318866694 +0800 ++++ ghc-8.6.5/libraries/gen_contents_index 2020-04-09 18:18:40.290722327 +0800 +@@ -47,6 +47,8 @@ + HADDOCK_ARGS="$HADDOCK_ARGS $HADDOCK_ARG" + done + else ++ if ! ls */*.haddock &>/dev/null; then exit 0; fi ++ + HADDOCK=/usr/bin/haddock + # We don't want the GHC API to swamp the index + HADDOCK_FILES=`ls -1 */*.haddock | grep -v '/ghc\.haddock' | sort` diff --git a/ghc.spec b/ghc.spec index 91e49f1..c47e015 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.6.5 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 102%{?dist} +Release: 103%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -64,6 +64,7 @@ Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) Patch1: ghc-gen_contents_index-haddock-path.patch Patch2: ghc-Cabal-install-PATH-warning.patch +Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch @@ -232,6 +233,7 @@ License: BSD Obsoletes: ghc-doc-cron < %{version}-%{release} Requires: ghc-compiler = %{version}-%{release} BuildArch: noarch +#Recommends: ghc-base-doc = %{base_ver}-%{release} %description doc-index The package enables re-indexing of installed library documention. @@ -322,6 +324,7 @@ packages to be automatically installed too. %setup -q -n %{name}-%{version} %{?with_testsuite:-b1} %patch1 -p1 -b .orig +%patch3 -p1 -b .orig %patch2 -p1 -b .orig %patch6 -p1 -b .orig @@ -574,11 +577,11 @@ make test %if %{with haddock} %transfiletriggerin doc-index -- %{ghc_html_libraries_dir} -%{ghc_html_libraries_dir}/gen_contents_index +env -C %{ghc_html_libraries_dir} ./gen_contents_index %end %transfiletriggerpostun doc-index -- %{ghc_html_libraries_dir} -%{ghc_html_libraries_dir}/gen_contents_index +env -C %{ghc_html_libraries_dir} ./gen_contents_index %end %endif @@ -681,8 +684,8 @@ make test %changelog -* Tue Mar 10 2020 Jens Petersen -- add bcond for dwarf info +* Thu Apr 9 2020 Jens Petersen - 8.6.5-103 +- fix running of gen_contents_index when no haddocks (#1813548) * Mon Feb 10 2020 Jens Petersen - 8.6.5-102 - rebuild against ghc-rpm-macros fixed for subpackage prof deps From 230c643c59cd5b07b6a5c5234e1e85a6a16f064a Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 9 Apr 2020 19:21:28 +0800 Subject: [PATCH 502/530] drop "recommends: ghc-base-doc" comment warning: Macro expanded in comment on line 236: %{base_ver}-%{release} --- ghc.spec | 1 - 1 file changed, 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index c47e015..b02cc00 100644 --- a/ghc.spec +++ b/ghc.spec @@ -233,7 +233,6 @@ License: BSD Obsoletes: ghc-doc-cron < %{version}-%{release} Requires: ghc-compiler = %{version}-%{release} BuildArch: noarch -#Recommends: ghc-base-doc = %{base_ver}-%{release} %description doc-index The package enables re-indexing of installed library documention. From 6130fa57e2f404a1b4a904619faba46f850525e7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 6 Jul 2020 15:38:46 +0800 Subject: [PATCH 503/530] use python3-sphinx also for rhel8 --- ghc.spec | 7 +++++-- 1 file changed, 5 insertions(+), 2 deletions(-) diff --git a/ghc.spec b/ghc.spec index b02cc00..21622f4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.6.5 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 103%{?dist} +Release: 104%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -135,7 +135,7 @@ BuildRequires: perl-interpreter BuildRequires: python3 %endif %if %{with manual} -%if 0%{?fedora} >= 31 +%if 0%{?fedora} >= 31 || 0%{?rhel} >= 8 BuildRequires: python3-sphinx %else BuildRequires: python2-sphinx @@ -683,6 +683,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Mon Jul 6 2020 Jens Petersen - 8.6.5-104 +- use python3-sphinx also for rhel8 + * Thu Apr 9 2020 Jens Petersen - 8.6.5-103 - fix running of gen_contents_index when no haddocks (#1813548) From d0354c8ff4492d7a64883fcb3109447c6ccbebab Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 14 Jul 2020 19:54:43 +0800 Subject: [PATCH 504/530] remove redundant unused ghc-configure-fix-sphinx-version-check.patch --- ghc-configure-fix-sphinx-version-check.patch | 11 ----------- 1 file changed, 11 deletions(-) delete mode 100644 ghc-configure-fix-sphinx-version-check.patch diff --git a/ghc-configure-fix-sphinx-version-check.patch b/ghc-configure-fix-sphinx-version-check.patch deleted file mode 100644 index c19da05..0000000 --- a/ghc-configure-fix-sphinx-version-check.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-8.2.2/configure.ac~ 2017-11-21 05:22:42.000000000 +0900 -+++ ghc-8.2.2/configure.ac 2018-05-28 12:37:35.296728423 +0900 -@@ -745,7 +745,7 @@ - AC_CACHE_CHECK([for version of sphinx-build], fp_cv_sphinx_version, - changequote(, )dnl - [if test -n "$SPHINXBUILD"; then -- fp_cv_sphinx_version=`"$SPHINXBUILD" --version 2>&1 | sed 's/Sphinx\( (sphinx-build)\)\? v\?\([0-9]\.[0-9]\.[0-9]\)/\2/' | head -n1`; -+ fp_cv_sphinx_version=`"$SPHINXBUILD" --version 2>&1 | sed 's/.* v\?\([0-9]\.[0-9]\.[0-9]\)/\1/' | head -n1`; - fi; - changequote([, ])dnl - ]) From e3a510e58ccf472d7548dd36467906f59b789f85 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 14 Jul 2020 23:34:59 +0800 Subject: [PATCH 505/530] rebase to 8.8.3 from ghc:8.8 --- ...12fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch | 92 --------------- ...41b3622e2e578d928f7513941aac9d873279.patch | 24 ---- Disable-unboxed-arrays.patch | 6 +- PprC-Add-support-for-adjacent-floats.patch | 69 ------------ add_-latomic_to_ghc-prim.patch | 54 --------- ...aaf6918bb2b497b83618dc4c270a0d231a1c.patch | 63 ----------- ghc.spec | 105 ++++++++---------- 7 files changed, 50 insertions(+), 363 deletions(-) delete mode 100644 3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch delete mode 100644 73ea41b3622e2e578d928f7513941aac9d873279.patch delete mode 100644 PprC-Add-support-for-adjacent-floats.patch delete mode 100644 add_-latomic_to_ghc-prim.patch delete mode 100644 e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch diff --git a/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch b/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch deleted file mode 100644 index 98a7925..0000000 --- a/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch +++ /dev/null @@ -1,92 +0,0 @@ -From 3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b Mon Sep 17 00:00:00 2001 -From: Ben Gamari -Date: Mon, 1 Jul 2019 11:03:33 -0400 -Subject: [PATCH] Call initgroups before setuid - -Previously we would fail to call initgroups before setuid'ing. This -meant that our groups we not be reset to reflect those our new user -belongs to. Fix this. ---- - cbits/runProcess.c | 32 +++++++++++++++++++++++++++++--- - include/runProcess.h | 4 ++++ - 2 files changed, 33 insertions(+), 3 deletions(-) - -diff --git a/cbits/runProcess.c b/cbits/runProcess.c -index 10794bc..84d5fd4 100644 ---- a/cbits/runProcess.c -+++ b/cbits/runProcess.c -@@ -33,6 +33,10 @@ static long max_fd = 0; - extern void blockUserSignals(void); - extern void unblockUserSignals(void); - -+// These are arbitrarily chosen -- JP -+#define forkSetgidFailed 124 -+#define forkSetuidFailed 125 -+ - // See #1593. The convention for the exit code when - // exec() fails seems to be 127 (gleened from C's - // system()), but there's no equivalent convention for -@@ -40,9 +44,8 @@ extern void unblockUserSignals(void); - #define forkChdirFailed 126 - #define forkExecFailed 127 - --// These are arbitrarily chosen -- JP --#define forkSetgidFailed 124 --#define forkSetuidFailed 125 -+#define forkGetpwuidFailed 128 -+#define forkInitgroupsFailed 129 - - __attribute__((__noreturn__)) - static void childFailed(int pipe, int failCode) { -@@ -182,6 +185,23 @@ runInteractiveProcess (char *const args[], - } - - if ( childUser) { -+ // Using setuid properly first requires that we initgroups. -+ // However, to do this we must know the username of the user we are -+ // switching to. -+ struct passwd pw; -+ struct passwd *res = NULL; -+ int buf_len = sysconf(_SC_GETPW_R_SIZE_MAX); -+ char *buf = malloc(buf_len); -+ gid_t suppl_gid = childGroup ? *childGroup : getgid(); -+ if ( getpwuid_r(*childUser, &pw, buf, buf_len, &res) != 0) { -+ childFailed(forkCommunicationFds[1], forkGetpwuidFailed); -+ } -+ if ( res == NULL ) { -+ childFailed(forkCommunicationFds[1], forkGetpwuidFailed); -+ } -+ if ( initgroups(res->pw_name, suppl_gid) != 0) { -+ childFailed(forkCommunicationFds[1], forkInitgroupsFailed); -+ } - if ( setuid( *childUser) != 0) { - // ERROR - childFailed(forkCommunicationFds[1], forkSetuidFailed); -@@ -330,6 +350,12 @@ runInteractiveProcess (char *const args[], - case forkSetuidFailed: - *failed_doing = "runInteractiveProcess: setuid"; - break; -+ case forkGetpwuidFailed: -+ *failed_doing = "runInteractiveProcess: getpwuid"; -+ break; -+ case forkInitgroupsFailed: -+ *failed_doing = "runInteractiveProcess: initgroups"; -+ break; - default: - *failed_doing = "runInteractiveProcess: unknown"; - break; -diff --git a/include/runProcess.h b/include/runProcess.h -index 3807389..dff3905 100644 ---- a/include/runProcess.h -+++ b/include/runProcess.h -@@ -21,6 +21,10 @@ - - #include - #include -+#if !(defined(_MSC_VER) || defined(__MINGW32__) || defined(_WIN32)) -+#include -+#include -+#endif - - #ifdef HAVE_FCNTL_H - #include diff --git a/73ea41b3622e2e578d928f7513941aac9d873279.patch b/73ea41b3622e2e578d928f7513941aac9d873279.patch deleted file mode 100644 index 5b8d646..0000000 --- a/73ea41b3622e2e578d928f7513941aac9d873279.patch +++ /dev/null @@ -1,24 +0,0 @@ -From 73ea41b3622e2e578d928f7513941aac9d873279 Mon Sep 17 00:00:00 2001 -From: Ben Gamari -Date: Mon, 1 Jul 2019 11:02:45 -0400 -Subject: [PATCH] Fix incorrect case fallthrough - -The error message lookup logic would fallthrough from the -forkSetuidFailed case into the default case, meaning that the error -message of the former would never be returned. ---- - cbits/runProcess.c | 1 + - 1 file changed, 1 insertion(+) - -diff --git a/cbits/runProcess.c b/cbits/runProcess.c -index c621158..10794bc 100644 ---- a/cbits/runProcess.c -+++ b/cbits/runProcess.c -@@ -329,6 +329,7 @@ runInteractiveProcess (char *const args[], - break; - case forkSetuidFailed: - *failed_doing = "runInteractiveProcess: setuid"; -+ break; - default: - *failed_doing = "runInteractiveProcess: unknown"; - break; diff --git a/Disable-unboxed-arrays.patch b/Disable-unboxed-arrays.patch index 17d81c5..4ccb16d 100644 --- a/Disable-unboxed-arrays.patch +++ b/Disable-unboxed-arrays.patch @@ -1,7 +1,5 @@ -Index: ghc-8.6.1/libraries/containers/include/containers.h -=================================================================== ---- ghc-8.6.1.orig/libraries/containers/include/containers.h -+++ ghc-8.6.1/libraries/containers/include/containers.h +--- ghc-8.8.0.20190721/libraries/containers/containers/include/containers.h~ 2019-06-26 20:39:26.000000000 +0000 ++++ ghc-8.8.0.20190721/libraries/containers/containers/include/containers.h 2019-07-27 08:55:10.747060247 +0000 @@ -35,7 +35,6 @@ #ifdef __GLASGOW_HASKELL__ diff --git a/PprC-Add-support-for-adjacent-floats.patch b/PprC-Add-support-for-adjacent-floats.patch deleted file mode 100644 index 3a297c7..0000000 --- a/PprC-Add-support-for-adjacent-floats.patch +++ /dev/null @@ -1,69 +0,0 @@ -From 35a897782b6b0a252da7fdcf4921198ad4e1d96c Mon Sep 17 00:00:00 2001 -From: James Clarke -Date: Thu, 22 Nov 2018 11:55:17 -0500 -Subject: [PATCH] UNREG: PprC: Add support for adjacent floats - -When two 32-bit floats are adjacent for a 64-bit target, there is no -padding between them to force alignment, so we must combine their bit -representations into a single word. - -Reviewers: bgamari, simonmar - -Reviewed By: simonmar - -Subscribers: rwbarton, carter - -GHC Trac Issues: #15853 - -Differential Revision: https://phabricator.haskell.org/D5306 ---- - compiler/cmm/PprC.hs | 24 +++++++++++++++++++++++- - 1 file changed, 23 insertions(+), 1 deletion(-) - -diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs -index 17fef7fc97..6ebfd20291 100644 ---- a/compiler/cmm/PprC.hs -+++ b/compiler/cmm/PprC.hs -@@ -512,9 +512,12 @@ pprLit1 other = pprLit other - pprStatics :: DynFlags -> [CmmStatic] -> [SDoc] - pprStatics _ [] = [] - pprStatics dflags (CmmStaticLit (CmmFloat f W32) : rest) -- -- floats are padded to a word by padLitToWord, see #1852 -+ -- odd numbers of floats are padded to a word by mkVirtHeapOffsetsWithPadding - | wORD_SIZE dflags == 8, CmmStaticLit (CmmInt 0 W32) : rest' <- rest - = pprLit1 (floatToWord dflags f) : pprStatics dflags rest' -+ -- adjacent floats aren't padded but combined into a single word -+ | wORD_SIZE dflags == 8, CmmStaticLit (CmmFloat g W32) : rest' <- rest -+ = pprLit1 (floatPairToWord dflags f g) : pprStatics dflags rest' - | wORD_SIZE dflags == 4 - = pprLit1 (floatToWord dflags f) : pprStatics dflags rest - | otherwise -@@ -1270,6 +1273,25 @@ floatToWord dflags r - , wORDS_BIGENDIAN dflags = 32 - | otherwise = 0 - -+floatPairToWord :: DynFlags -> Rational -> Rational -> CmmLit -+floatPairToWord dflags r1 r2 -+ = runST (do -+ arr <- newArray_ ((0::Int),1) -+ writeArray arr 0 (fromRational r1) -+ writeArray arr 1 (fromRational r2) -+ arr' <- castFloatToWord32Array arr -+ w32_1 <- readArray arr' 0 -+ w32_2 <- readArray arr' 1 -+ return (pprWord32Pair w32_1 w32_2) -+ ) -+ where pprWord32Pair w32_1 w32_2 -+ | wORDS_BIGENDIAN dflags = -+ CmmInt ((shiftL i1 32) .|. i2) W64 -+ | otherwise = -+ CmmInt ((shiftL i2 32) .|. i1) W64 -+ where i1 = toInteger w32_1 -+ i2 = toInteger w32_2 -+ - doubleToWords :: DynFlags -> Rational -> [CmmLit] - doubleToWords dflags r - = runST (do --- -2.19.2 - diff --git a/add_-latomic_to_ghc-prim.patch b/add_-latomic_to_ghc-prim.patch deleted file mode 100644 index 71e4ddb..0000000 --- a/add_-latomic_to_ghc-prim.patch +++ /dev/null @@ -1,54 +0,0 @@ -commit ce3897ffd6e7c8b8f36b8e920168bac8c7f836ae -Author: Ilias Tsitsimpis -Date: Tue Sep 18 17:45:17 2018 +0200 - - Fix check whether GCC supports __atomic_ builtins - - Summary: - C11 atomics are never used because: - - * The program used for checking whether GCC supports - __atomic_ builtins fails with the following error: - - ``` - error: size mismatch in argument 2 of `__atomic_load` - int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; } - ``` - - * There is a typo when checking if CONF_GCC_SUPPORTS__ATOMICS equals YES, - resulting in PRIM_CFLAGS and PRIM_EXTRA_LIBRARIES never being set. - - Reviewers: bgamari - - Reviewed By: bgamari - - Subscribers: rwbarton, erikd, carter - - Differential Revision: https://phabricator.haskell.org/D5154 - -Index: b/libraries/ghc-prim/aclocal.m4 -=================================================================== ---- a/libraries/ghc-prim/aclocal.m4 -+++ b/libraries/ghc-prim/aclocal.m4 -@@ -5,7 +5,7 @@ AC_DEFUN([FP_GCC_SUPPORTS__ATOMICS], - [ - AC_REQUIRE([AC_PROG_CC]) - AC_MSG_CHECKING([whether GCC supports __atomic_ builtins]) -- echo 'int test(int *x) { int y; __atomic_load(&x, &y, __ATOMIC_SEQ_CST); return x; }' > conftest.c -+ echo 'int test(int *x) { int y; __atomic_load(x, &y, __ATOMIC_SEQ_CST); return y; }' > conftest.c - if $CC -c conftest.c > /dev/null 2>&1; then - CONF_GCC_SUPPORTS__ATOMICS=YES - AC_MSG_RESULT([yes]) -Index: b/libraries/ghc-prim/configure.ac -=================================================================== ---- a/libraries/ghc-prim/configure.ac -+++ b/libraries/ghc-prim/configure.ac -@@ -8,7 +8,7 @@ dnl unregisterised, Sparc, and PPC ba - FP_GCC_SUPPORTS__ATOMICS - AC_DEFINE([HAVE_C11_ATOMICS], [$CONF_GCC_SUPPORTS__ATOMICS], [Does GCC support __atomic primitives?]) - --if test "x$CONF_GCC_SUPPORTS__ATOMICS" = YES -+if test "$CONF_GCC_SUPPORTS__ATOMICS" = "YES" - then PRIM_CFLAGS=-DHAVE_C11_ATOMICS - PRIM_EXTRA_LIBRARIES=atomic - fi diff --git a/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch b/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch deleted file mode 100644 index 8824289..0000000 --- a/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch +++ /dev/null @@ -1,63 +0,0 @@ -From: Sergei Trofimovich -Date: Wed, 18 Jul 2018 22:36:58 +0000 (+0100) -Subject: fix osReserveHeapMemory block alignment -X-Git-Url: https://git.haskell.org/ghc.git/commitdiff_plain/e175aaf6918bb2b497b83618dc4c270a0d231a1c - -fix osReserveHeapMemory block alignment - -Before the change osReserveHeapMemory() attempted -to allocate chunks of memory via osTryReserveHeapMemory() -not multiple of MBLOCK_SIZE in the following fallback code: - -``` - if (at == NULL) { - *len -= *len / 8; -``` - -and caused assertion failure: - -``` -$ make fulltest TEST=T11607 WAY=threaded1 -T11607: internal error: ASSERTION FAILED: file rts/posix/OSMem.c, line 457 - (GHC version 8.7.20180716 for riscv64_unknown_linux) - -``` - -The change applies alignment mask before each MBLOCK allocation attempt -and fixes WAY=threaded1 test failures on qemu-riscv64. - -Signed-off-by: Sergei Trofimovich - -Test Plan: run 'make fulltest WAY=threaded1' - -Reviewers: simonmar, bgamari, erikd - -Reviewed By: simonmar - -Subscribers: rwbarton, thomie, carter - -Differential Revision: https://phabricator.haskell.org/D4982 ---- - -Index: b/rts/posix/OSMem.c -=================================================================== ---- a/rts/posix/OSMem.c -+++ b/rts/posix/OSMem.c -@@ -476,6 +476,8 @@ osTryReserveHeapMemory (W_ len, void *hi - void *base, *top; - void *start, *end; - -+ ASSERT((len & ~MBLOCK_MASK) == len); -+ - /* We try to allocate len + MBLOCK_SIZE, - because we need memory which is MBLOCK_SIZE aligned, - and then we discard what we don't need */ -@@ -552,6 +554,8 @@ void *osReserveHeapMemory(void *startAdd - - attempt = 0; - while (1) { -+ *len &= ~MBLOCK_MASK; -+ - if (*len < MBLOCK_SIZE) { - // Give up if the system won't even give us 16 blocks worth of heap - barf("osReserveHeapMemory: Failed to allocate heap storage"); diff --git a/ghc.spec b/ghc.spec index 21622f4..abe6b25 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.12.0.0 +%global base_ver 4.13.0.0 # build profiling libraries # build haddock @@ -37,27 +37,28 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.6 needs llvm-6.0 -%global llvm_major 6.0 +# 8.8 needs llvm-7.0 +%global llvm_major 7.0 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc -Version: 8.6.5 +Version: 8.8.3 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 104%{?dist} +Release: 105%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport URL: https://haskell.org/ghc/ -Source0: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-src.tar.xz +Source0: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-src.tar.xz %if %{with testsuite} -Source1: https://downloads.haskell.org/~ghc/%{ghc_release}/ghc-%{version}-testsuite.tar.xz +Source1: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-testsuite.tar.xz %endif +Source2: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-src.tar.xz.sig Source5: ghc-pkg.man Source6: haddock.man Source7: runghc.man @@ -68,10 +69,6 @@ Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch -# https://github.com/haskell/process/pull/148 -Patch10: https://github.com/haskell/process/commit/73ea41b3622e2e578d928f7513941aac9d873279.patch -Patch11: https://github.com/haskell/process/commit/3e0812fe9d3f4712638a1c4c49bf2b2a7dc4311b.patch - # Arch dependent patches # arm @@ -80,39 +77,27 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # for unregisterized (s390x) # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch -# https://gitlab.haskell.org/ghc/ghc/issues/15853 -# https://phabricator.haskell.org/D5306 (in 8.8) -# https://gitlab.haskell.org/ghc/ghc/commit/35a897782b6b0a252da7fdcf4921198ad4e1d96c.patch -# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/PprC-Add-support-for-adjacent-floats -Patch17: PprC-Add-support-for-adjacent-floats.patch # bigendian (s390x and ppc64) -# fix haddock-library # https://gitlab.haskell.org/ghc/ghc/issues/15411 # https://gitlab.haskell.org/ghc/ghc/issues/16505 # https://bugzilla.redhat.com/show_bug.cgi?id=1651448 # https://ghc.haskell.org/trac/ghc/ticket/15914 -Patch18: https://gitlab.haskell.org/ghc/ghc/uploads/5deb133cf910e9e0ca9ad9fe53f7383a/Disable-unboxed-arrays.patch +# https://gitlab.haskell.org/ghc/ghc/issues/16973 +# https://bugzilla.redhat.com/show_bug.cgi?id=1733030 +Patch18: Disable-unboxed-arrays.patch # Debian patches: Patch24: buildpath-abi-stability.patch Patch26: no-missing-haddock-file-warning.patch Patch28: x32-use-native-x86_64-insn.patch -# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/add_-latomic_to_ghc-prim -Patch30: add_-latomic_to_ghc-prim.patch -# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch -Patch32: https://salsa.debian.org/haskell-team/DHG_packages/raw/master/p/ghc/debian/patches/e175aaf6918bb2b497b83618dc4c270a0d231a1c.patch -# https://gitlab.haskell.org/ghc/ghc/issues/15913 -# remove after Fedora default moves to 8.6 -# https://salsa.debian.org/haskell-team/DHG_packages/blob/master/p/ghc/debian/patches/fix-build-using-unregisterized-v8.4 -Patch34: fix-build-using-unregisterized-v8.4.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel # see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -BuildRequires: ghc-compiler +BuildRequires: ghc-compiler > 8.4 # for ABI hash checking %if %{with abicheck} BuildRequires: ghc @@ -125,6 +110,7 @@ BuildRequires: ghc-directory-devel BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel BuildRequires: ghc-transformers-devel +BuildRequires: alex BuildRequires: gmp-devel BuildRequires: libffi-devel BuildRequires: make @@ -135,14 +121,10 @@ BuildRequires: perl-interpreter BuildRequires: python3 %endif %if %{with manual} -%if 0%{?fedora} >= 31 || 0%{?rhel} >= 8 BuildRequires: python3-sphinx -%else -BuildRequires: python2-sphinx -%endif %endif %ifarch %{ghc_llvm_archs} -%if 0%{?fedora} >= 29 +%if 0%{?fedora} > 29 BuildRequires: llvm%{llvm_major} %else BuildRequires: llvm >= %{llvm_major} @@ -155,6 +137,9 @@ BuildRequires: elfutils-devel # patch12 BuildRequires: autoconf, automake %endif +%if %{without quickbuild} +#BuildRequires: gnupg2 +%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} Requires: ghc-devel = %{version}-%{release} @@ -199,6 +184,7 @@ License: BSD Requires: gcc%{?_isa} Requires: ghc-base-devel%{?_isa} = %{base_ver}-%{release} %if %{without haddock} +# added during f31 Obsoletes: ghc-doc-index < %{version}-%{release} %endif %ifarch %{ghc_llvm_archs} @@ -257,30 +243,32 @@ This package provides the User Guide and Haddock manual. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-2.4.0.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.3.0 +%ghc_lib_subpackage -d -l BSD Cabal-3.0.1.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} -%ghc_lib_subpackage -d -l BSD binary-0.8.6.0 -%ghc_lib_subpackage -d -l BSD bytestring-0.10.8.2 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.0.1 +%ghc_lib_subpackage -d -l BSD binary-0.8.7.0 +%ghc_lib_subpackage -d -l BSD bytestring-0.10.10.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.2.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.3.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 %ghc_lib_subpackage -d -l BSD filepath-1.4.2.1 %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 %ghc_lib_subpackage -d -l BSD ghc-heap-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD haskeline-0.7.4.3 +# see below for ghc-prim +%ghc_lib_subpackage -d -l BSD haskeline-0.7.5.0 %ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 -%ghc_lib_subpackage -d -l %BSDHaskellReport libiserv-8.6.3 +# see below for integer-gmp +%ghc_lib_subpackage -d -l %BSDHaskellReport libiserv-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD mtl-2.2.2 -%ghc_lib_subpackage -d -l BSD parsec-3.1.13.0 +%ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.5.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.8.0 %ghc_lib_subpackage -d -l BSD stm-2.5.0.0 -%ghc_lib_subpackage -d -l BSD template-haskell-2.14.0.0 -%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.2 -%ghc_lib_subpackage -d -l BSD text-1.2.3.1 -%ghc_lib_subpackage -d -l BSD time-1.8.0.2 +%ghc_lib_subpackage -d -l BSD template-haskell-2.15.0.0 +%ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 +%ghc_lib_subpackage -d -l BSD text-1.2.4.0 +%ghc_lib_subpackage -d -l BSD time-1.9.3 %ghc_lib_subpackage -d -l BSD transformers-0.5.6.2 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{with haddock} @@ -320,6 +308,9 @@ packages to be automatically installed too. %prep +%if %{without quickbuild} +#%%{gpgverify} --keyring='%{SOURCE3}' --signature='%{SOURCE2}' --data='%{SOURCE0}' +%endif %setup -q -n %{name}-%{version} %{?with_testsuite:-b1} %patch1 -p1 -b .orig @@ -330,20 +321,12 @@ packages to be automatically installed too. rm -r libffi-tarballs -( -cd libraries/process -%patch10 -p1 -b .orig10 -%patch11 -p1 -b .orig11 -) - %ifarch armv7hl %patch12 -p1 -b .orig %endif %ifarch %{ghc_unregisterized_arches} %patch15 -p1 -b .orig -%patch17 -p1 -b .orig -%patch34 -p1 -b .orig %endif # bigendian @@ -355,8 +338,6 @@ cd libraries/process %patch24 -p1 -b .orig %patch26 -p1 -b .orig %patch28 -p1 -b .orig -%patch30 -p1 -b .orig -%patch32 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{with haddock} @@ -450,6 +431,9 @@ done sed -i -e 's!^library-dirs: %{ghclibdir}/rts!&\ndynamic-library-dirs: %{_ghcdynlibdir}!' %{buildroot}%{ghclibdir}/package.conf.d/rts.conf %endif +# containers src moved to a subdir +cp -p libraries/containers/containers/LICENSE libraries/containers/LICENSE + # libraries licenses rm %{buildroot}%{ghc_html_libraries_dir}/{ghc-prim,integer-gmp}-*/LICENSE mkdir -p %{buildroot}%{_ghclicensedir} @@ -571,7 +555,6 @@ make test %transfiletriggerpostun compiler -- %{ghclibdir}/package.conf.d %ghc_pkg_recache %end -%endif %if %{with haddock} @@ -583,6 +566,7 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index env -C %{ghc_html_libraries_dir} ./gen_contents_index %end %endif +%endif %files @@ -648,6 +632,7 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %ghost %{ghc_html_dir}/libraries/haddock-util.js %ghost %{ghc_html_dir}/libraries/hslogo-16.png %ghost %{ghc_html_dir}/libraries/index*.html +%ghost %{ghc_html_dir}/libraries/linuwial.css %ghost %{ghc_html_dir}/libraries/minus.gif %ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif @@ -683,6 +668,12 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Tue Jul 14 2020 Jens Petersen - 8.8.3-105 +- rebase to 8.8.3 from ghc:8.8 module stream +- https://downloads.haskell.org/ghc/8.8.1/docs/html/users_guide/8.8.1-notes.html +- https://downloads.haskell.org/ghc/8.8.2/docs/html/users_guide/8.8.2-notes.html +- https://downloads.haskell.org/ghc/8.8.3/docs/html/users_guide/8.8.3-notes.html + * Mon Jul 6 2020 Jens Petersen - 8.6.5-104 - use python3-sphinx also for rhel8 From 0a7f55360c036a942a109c6faf9c7a5157a81052 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 15 Jul 2020 03:03:49 +0800 Subject: [PATCH 506/530] add fix-build-using-unregisterised-v8.6.patch from Debian --- fix-build-using-unregisterised-v8.6.patch | 31 +++++++++++++++++++++++ ghc.spec | 2 ++ 2 files changed, 33 insertions(+) create mode 100644 fix-build-using-unregisterised-v8.6.patch diff --git a/fix-build-using-unregisterised-v8.6.patch b/fix-build-using-unregisterised-v8.6.patch new file mode 100644 index 0000000..3147c68 --- /dev/null +++ b/fix-build-using-unregisterised-v8.6.patch @@ -0,0 +1,31 @@ +Description: Allow unregisterised ghc-8.6 to build newer GHC + Commit af9b744bbf1 introduced a regression stopping existing unregisterised + compilers from being able to compile newer versions of GHC. The problem is + that the bootstrap compiler uses the newer `includes/stg/MiscClosures.h` file + where some defines have been renamed, resulting in the following error: +. + error: ‘stg_atomicModifyMutVarzh’ undeclared (first use in this function); did you mean ‘stg_atomicModifyMutVar2zh’? +. + For more information, see https://gitlab.haskell.org/ghc/ghc/issues/17111. +. + This patch can be removed, once ghc-8.6 is no longer the bootstrap compiler. +Author: Ilias Tsitsimpis +Bug: https://gitlab.haskell.org/ghc/ghc/issues/17111 + +Index: b/includes/stg/MiscClosures.h +=================================================================== +--- a/includes/stg/MiscClosures.h ++++ b/includes/stg/MiscClosures.h +@@ -390,8 +390,12 @@ RTS_FUN_DECL(stg_copySmallMutableArrayzh + RTS_FUN_DECL(stg_casSmallArrayzh); + + RTS_FUN_DECL(stg_newMutVarzh); ++#if __GLASGOW_HASKELL__ < 808 ++RTS_FUN_DECL(stg_atomicModifyMutVarzh); ++#else + RTS_FUN_DECL(stg_atomicModifyMutVar2zh); + RTS_FUN_DECL(stg_atomicModifyMutVarzuzh); ++#endif + RTS_FUN_DECL(stg_casMutVarzh); + + RTS_FUN_DECL(stg_isEmptyMVarzh); diff --git a/ghc.spec b/ghc.spec index abe6b25..17074df 100644 --- a/ghc.spec +++ b/ghc.spec @@ -77,6 +77,7 @@ Patch12: ghc-armv7-VFPv3D16--NEON.patch # for unregisterized (s390x) # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch +Patch16: fix-build-using-unregisterised-v8.6.patch # bigendian (s390x and ppc64) # https://gitlab.haskell.org/ghc/ghc/issues/15411 @@ -327,6 +328,7 @@ rm -r libffi-tarballs %ifarch %{ghc_unregisterized_arches} %patch15 -p1 -b .orig +%patch16 -p1 -b .orig %endif # bigendian From af8d45ddda3c0937d1bd7c968f161f2cb2137a43 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 15 Jul 2020 12:00:13 +0800 Subject: [PATCH 507/530] update sources for 8.8.3 --- .gitignore | 2 ++ sources | 3 ++- 2 files changed, 4 insertions(+), 1 deletion(-) diff --git a/.gitignore b/.gitignore index 33b3d92..d629921 100644 --- a/.gitignore +++ b/.gitignore @@ -27,3 +27,5 @@ testsuite-6.12.3.tar.bz2 /ghc-8.2.2-testsuite.tar.xz /ghc-8.4.4-src.tar.xz /ghc-8.6.5-src.tar.xz +/ghc-8.8.3-src.tar.xz +/ghc-8.8.3-src.tar.xz.sig diff --git a/sources b/sources index 3790399..929e4c9 100644 --- a/sources +++ b/sources @@ -1 +1,2 @@ -SHA512 (ghc-8.6.5-src.tar.xz) = c08a7480200cb99e1ffbe4ce7669f552b1054054966f7e7efcbc5f98af8032e1249fa391c4fc4c7d62cc8e0be5d17fa05845177f3cea3dbcf86e6c92d40fc0f9 +SHA512 (ghc-8.8.3-src.tar.xz) = 87e6c991c1b028f82ff5ca99bee6b4b2f4014ab2bb13aa8a3fdf80243c55a06020868ec051a5a554f2f11c4598b7275b17a55b9c4ea17816fcbc3450742e29ed +SHA512 (ghc-8.8.3-src.tar.xz.sig) = cc906acb89633d6f241228b1f40b4a8d6849ac4f1f3a9414388d0f14a4bd41ed65856d9b9c6212818fbb71d53a30fc64d3b5d0b85ecb3338af2de76e0612ebd4 From 50b4c3c856b0ce0c76c9e303d3c3aa28333c0be3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Jul 2020 15:19:40 +0800 Subject: [PATCH 508/530] correct oversized tarball --- sources | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/sources b/sources index 929e4c9..e0a19a5 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -SHA512 (ghc-8.8.3-src.tar.xz) = 87e6c991c1b028f82ff5ca99bee6b4b2f4014ab2bb13aa8a3fdf80243c55a06020868ec051a5a554f2f11c4598b7275b17a55b9c4ea17816fcbc3450742e29ed +SHA512 (ghc-8.8.3-src.tar.xz) = 7db0d820a288e56bd32935cc03584295900605f6e7cac6fe6adcb3ec6c24d8d2cebf7a8efa421f2d2fa192602d7f24dfad1ddeeba252455e4cb8baa9889dcaa9 SHA512 (ghc-8.8.3-src.tar.xz.sig) = cc906acb89633d6f241228b1f40b4a8d6849ac4f1f3a9414388d0f14a4bd41ed65856d9b9c6212818fbb71d53a30fc64d3b5d0b85ecb3338af2de76e0612ebd4 From eec49f6fa259a49a52d21e7ccc5d1f8b9fe7e22d Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 16 Jul 2020 21:29:42 +0800 Subject: [PATCH 509/530] 8.8.4 bugfix release --- .gitignore | 2 ++ ghc.spec | 13 +++++++++---- sources | 4 ++-- 3 files changed, 13 insertions(+), 6 deletions(-) diff --git a/.gitignore b/.gitignore index d629921..3ac4eb6 100644 --- a/.gitignore +++ b/.gitignore @@ -29,3 +29,5 @@ testsuite-6.12.3.tar.bz2 /ghc-8.6.5-src.tar.xz /ghc-8.8.3-src.tar.xz /ghc-8.8.3-src.tar.xz.sig +/ghc-8.8.4-src.tar.xz.sig +/ghc-8.8.4-src.tar.xz diff --git a/ghc.spec b/ghc.spec index 17074df..d23a5f8 100644 --- a/ghc.spec +++ b/ghc.spec @@ -44,12 +44,12 @@ %global ghc_unregisterized_arches s390 s390x %{mips} Name: ghc -Version: 8.8.3 +Version: 8.8.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 105%{?dist} +Release: 106%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -248,7 +248,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %ghc_lib_subpackage -d -l BSD binary-0.8.7.0 -%ghc_lib_subpackage -d -l BSD bytestring-0.10.10.0 +%ghc_lib_subpackage -d -l BSD bytestring-0.10.10.1 %ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.2.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 @@ -264,7 +264,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD mtl-2.2.2 %ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.8.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.9.0 %ghc_lib_subpackage -d -l BSD stm-2.5.0.0 %ghc_lib_subpackage -d -l BSD template-haskell-2.15.0.0 %ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 @@ -670,6 +670,11 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Thu Jul 16 2020 Jens Petersen - 8.8.4-106 +- 8.8.4 bugfix releases +- https://downloads.haskell.org/ghc/8.8.4/docs/html/users_guide/8.8.4-notes.html +- bytestring-0.10.10.1 and process-1.6.9.0 + * Tue Jul 14 2020 Jens Petersen - 8.8.3-105 - rebase to 8.8.3 from ghc:8.8 module stream - https://downloads.haskell.org/ghc/8.8.1/docs/html/users_guide/8.8.1-notes.html diff --git a/sources b/sources index e0a19a5..579d80e 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -SHA512 (ghc-8.8.3-src.tar.xz) = 7db0d820a288e56bd32935cc03584295900605f6e7cac6fe6adcb3ec6c24d8d2cebf7a8efa421f2d2fa192602d7f24dfad1ddeeba252455e4cb8baa9889dcaa9 -SHA512 (ghc-8.8.3-src.tar.xz.sig) = cc906acb89633d6f241228b1f40b4a8d6849ac4f1f3a9414388d0f14a4bd41ed65856d9b9c6212818fbb71d53a30fc64d3b5d0b85ecb3338af2de76e0612ebd4 +SHA512 (ghc-8.8.4-src.tar.xz.sig) = 1ed2e64e8b75a147d7c66b0018119f54ac740131b6f74612aa975c9120d8f7a8a2286829cef22ef2cd16262af0604659daa41c09ef3bdec6c22b8d086fbc1166 +SHA512 (ghc-8.8.4-src.tar.xz) = efd23bd819f7429486696a3a929a040471db7ea8a2d1f1d832e4cf0825b9e1e0c5e6ecad0ab8376f58b74e9c28c1d2f773bd126596d6d853c9e57d57e5ceb090 From 6d71e63ad790fe8ec1586c430a20a4bcb064e5ef Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Mon, 27 Jul 2020 18:40:52 +0000 Subject: [PATCH 510/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_33_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index d23a5f8..a0763dd 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.8.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 106%{?dist} +Release: 107%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -670,6 +670,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Mon Jul 27 2020 Fedora Release Engineering - 8.8.4-107 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_33_Mass_Rebuild + * Thu Jul 16 2020 Jens Petersen - 8.8.4-106 - 8.8.4 bugfix releases - https://downloads.haskell.org/ghc/8.8.4/docs/html/users_guide/8.8.4-notes.html From ea34541a5898521fdda243568abbf6a7f3beb7de Mon Sep 17 00:00:00 2001 From: Troy Dawson Date: Wed, 12 Aug 2020 20:01:37 +0000 Subject: [PATCH 511/530] Remove un-needed %if This %if statement is no longer needed because it addresses unsupported Fedora releases. This also causes ELN builds to not be the same as Fedora Rawhide builds. Signed-off-by: Troy Dawson --- ghc.spec | 4 ---- 1 file changed, 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index a0763dd..77b95e2 100644 --- a/ghc.spec +++ b/ghc.spec @@ -125,11 +125,7 @@ BuildRequires: python3 BuildRequires: python3-sphinx %endif %ifarch %{ghc_llvm_archs} -%if 0%{?fedora} > 29 BuildRequires: llvm%{llvm_major} -%else -BuildRequires: llvm >= %{llvm_major} -%endif %endif %if %{with dwarf} BuildRequires: elfutils-devel From 74b443ac38e31653c0318d48fa16c156384acd34 Mon Sep 17 00:00:00 2001 From: Troy Dawson Date: Tue, 18 Aug 2020 15:12:05 +0000 Subject: [PATCH 512/530] Remove all un-needed %if Remove all %if's that deal with old fedora releases. --- ghc.spec | 9 --------- 1 file changed, 9 deletions(-) diff --git a/ghc.spec b/ghc.spec index 77b95e2..5ac2057 100644 --- a/ghc.spec +++ b/ghc.spec @@ -185,11 +185,7 @@ Requires: ghc-base-devel%{?_isa} = %{base_ver}-%{release} Obsoletes: ghc-doc-index < %{version}-%{release} %endif %ifarch %{ghc_llvm_archs} -%if 0%{?fedora} >= 29 Requires: llvm%{llvm_major} -%else -Requires: llvm >= %{llvm_major} -%endif %endif %description compiler @@ -387,12 +383,7 @@ EOF autoreconf %endif -%if 0%{?fedora} > 28 %ghc_set_gcc_flags -%else -export CFLAGS="${CFLAGS:-%optflags}" -export LDFLAGS="${LDFLAGS:-%{?__global_ldflags}}" -%endif # for ghc >= 8.2 export CC=%{_bindir}/gcc From b3048e03e01cc2458f34d9c9c3cc4f8a99f70152 Mon Sep 17 00:00:00 2001 From: Troy Dawson Date: Wed, 9 Sep 2020 15:20:40 +0000 Subject: [PATCH 513/530] Bump release --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5ac2057..23c68e6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.8.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 107%{?dist} +Release: 108%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -657,6 +657,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Tue Aug 18 2020 Troy Dawson - 8.8.4-108 +- Cleanup old %if statements + * Mon Jul 27 2020 Fedora Release Engineering - 8.8.4-107 - Rebuilt for https://fedoraproject.org/wiki/Fedora_33_Mass_Rebuild From 3ea16b273c646a71a7ba371169332838d5ae7df7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sat, 12 Dec 2020 23:42:02 +0800 Subject: [PATCH 514/530] Add riscv64 to ghc_unregisterized_arches (David Abdurachmanov) --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 23c68e6..5e3c09c 100644 --- a/ghc.spec +++ b/ghc.spec @@ -41,7 +41,7 @@ %global llvm_major 7.0 %global ghc_llvm_archs armv7hl aarch64 -%global ghc_unregisterized_arches s390 s390x %{mips} +%global ghc_unregisterized_arches s390 s390x %{mips} riscv64 Name: ghc Version: 8.8.4 @@ -657,6 +657,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Wed Dec 02 2020 David Abdurachmanov +- Add riscv64 to ghc_unregisterized_arches + * Tue Aug 18 2020 Troy Dawson - 8.8.4-108 - Cleanup old %if statements From c44a7b9a9fa3da18e9f50d51cd9fd92349afb51e Mon Sep 17 00:00:00 2001 From: Fedora Release Engineering Date: Tue, 26 Jan 2021 06:44:33 +0000 Subject: [PATCH 515/530] - Rebuilt for https://fedoraproject.org/wiki/Fedora_34_Mass_Rebuild Signed-off-by: Fedora Release Engineering --- ghc.spec | 5 ++++- 1 file changed, 4 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 5e3c09c..6527bb4 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.8.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 108%{?dist} +Release: 109%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -657,6 +657,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Tue Jan 26 2021 Fedora Release Engineering - 8.8.4-109 +- Rebuilt for https://fedoraproject.org/wiki/Fedora_34_Mass_Rebuild + * Wed Dec 02 2020 David Abdurachmanov - Add riscv64 to ghc_unregisterized_arches From 2c6671df3089d2b5899b226168b9658647008ab5 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 30 Apr 2021 12:25:50 +0800 Subject: [PATCH 516/530] ghc-compiler now requires ghc-filesystem for html docdirs --- ghc.spec | 9 +++++---- 1 file changed, 5 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 6527bb4..828e1a9 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.8.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 109%{?dist} +Release: 110%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -180,6 +180,7 @@ Summary: GHC compiler and utilities License: BSD Requires: gcc%{?_isa} Requires: ghc-base-devel%{?_isa} = %{base_ver}-%{release} +Requires: ghc-filesystem %if %{without haddock} # added during f31 Obsoletes: ghc-doc-index < %{version}-%{release} @@ -601,8 +602,6 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %{ghclibdir}/platformConstants %{ghclibdir}/settings %{ghclibdir}/template-hsc.h -%dir %{_docdir}/ghc -%dir %{ghc_html_dir} %{_mandir}/man1/ghc-pkg.1* %{_mandir}/man1/haddock.1* %{_mandir}/man1/runghc.1* @@ -613,7 +612,6 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %{ghclibdir}/bin/haddock %{ghclibdir}/html %{ghclibdir}/latex -%dir %{ghc_html_dir}/libraries %{ghc_html_dir}/libraries/gen_contents_index %{ghc_html_dir}/libraries/prologue.txt %ghost %{ghc_html_dir}/libraries/doc-index*.html @@ -657,6 +655,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Tue May 25 2021 Jens Petersen - 8.8.4-110 +- ghc-compiler now requires ghc-filesystem for html docdirs + * Tue Jan 26 2021 Fedora Release Engineering - 8.8.4-109 - Rebuilt for https://fedoraproject.org/wiki/Fedora_34_Mass_Rebuild From f7cbc14ee447f1ea5b6f5c206240425dd2f463f7 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 1 Jul 2021 00:37:53 +0800 Subject: [PATCH 517/530] fix build with sphinx4 (#1977317) use rawstring in conf.py (already in ghc-9) --- ghc-userguide-sphinx4.patch | 11 +++++++++++ ghc.spec | 14 ++++++++++---- 2 files changed, 21 insertions(+), 4 deletions(-) create mode 100644 ghc-userguide-sphinx4.patch diff --git a/ghc-userguide-sphinx4.patch b/ghc-userguide-sphinx4.patch new file mode 100644 index 0000000..8c31df1 --- /dev/null +++ b/ghc-userguide-sphinx4.patch @@ -0,0 +1,11 @@ +--- ghc-8.8.4/docs/users_guide/conf.py~ 2020-07-09 00:43:03.000000000 +0800 ++++ ghc-8.8.4/docs/users_guide/conf.py 2021-07-01 00:09:03.537324304 +0800 +@@ -77,7 +77,7 @@ + latex_elements = { + 'inputenc': '', + 'utf8extra': '', +- 'preamble': ''' ++ 'preamble': r''' + \usepackage{fontspec} + \usepackage{makeidx} + \setsansfont{DejaVu Sans} diff --git a/ghc.spec b/ghc.spec index 828e1a9..b1b1eb3 100644 --- a/ghc.spec +++ b/ghc.spec @@ -49,7 +49,7 @@ Version: 8.8.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 110%{?dist} +Release: 111%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -63,11 +63,13 @@ Source5: ghc-pkg.man Source6: haddock.man Source7: runghc.man # absolute haddock path (was for html/libraries -> libraries) -Patch1: ghc-gen_contents_index-haddock-path.patch -Patch2: ghc-Cabal-install-PATH-warning.patch -Patch3: ghc-gen_contents_index-nodocs.patch +Patch1: ghc-gen_contents_index-haddock-path.patch +Patch2: ghc-Cabal-install-PATH-warning.patch +Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch +# https://bugzilla.redhat.com/show_bug.cgi?id=1977317 +Patch7: ghc-userguide-sphinx4.patch # Arch dependent patches @@ -312,6 +314,7 @@ packages to be automatically installed too. %patch2 -p1 -b .orig %patch6 -p1 -b .orig +%patch7 -p1 -b .orig rm -r libffi-tarballs @@ -655,6 +658,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Wed Jun 30 2021 Jens Petersen - 8.8.4-111 +- fix build with sphinx4 (#1977317) + * Tue May 25 2021 Jens Petersen - 8.8.4-110 - ghc-compiler now requires ghc-filesystem for html docdirs From 867f1588757381fbe22a568b81f49a0ba119eac3 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 11 Jul 2021 21:27:39 +0800 Subject: [PATCH 518/530] rebase to 8.10.5 from ghc:8.10 --- .gitignore | 2 + ...25fa5f0fce033b529547e0658076e26f4cda.patch | 39 +++++++++++ buildpath-abi-stability.patch | 12 ++-- ghc.spec | 65 ++++++++++--------- sources | 4 +- 5 files changed, 86 insertions(+), 36 deletions(-) create mode 100644 296f25fa5f0fce033b529547e0658076e26f4cda.patch diff --git a/.gitignore b/.gitignore index 3ac4eb6..22069ca 100644 --- a/.gitignore +++ b/.gitignore @@ -31,3 +31,5 @@ testsuite-6.12.3.tar.bz2 /ghc-8.8.3-src.tar.xz.sig /ghc-8.8.4-src.tar.xz.sig /ghc-8.8.4-src.tar.xz +/ghc-8.10.5-src.tar.xz.sig +/ghc-8.10.5-src.tar.xz diff --git a/296f25fa5f0fce033b529547e0658076e26f4cda.patch b/296f25fa5f0fce033b529547e0658076e26f4cda.patch new file mode 100644 index 0000000..813c500 --- /dev/null +++ b/296f25fa5f0fce033b529547e0658076e26f4cda.patch @@ -0,0 +1,39 @@ +From 296f25fa5f0fce033b529547e0658076e26f4cda Mon Sep 17 00:00:00 2001 +From: Adam Sandberg Ericsson +Date: Wed, 28 Apr 2021 20:11:52 +0100 +Subject: [PATCH] rts: export allocateWrite, freeWrite and markExec #19763 + +(cherry picked from commit 2d2985a79eec3d6ae9aee96b264c97c2b158f196) +--- + rts/RtsSymbols.c | 10 ++++++++++ + 1 file changed, 10 insertions(+) + +diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c +index 9ca696c27c4..d5b8cc5fece 100644 +--- a/rts/RtsSymbols.c ++++ b/rts/RtsSymbols.c +@@ -539,11 +539,21 @@ + #define RTS_PROF_SYMBOLS /* empty */ + #endif + ++#if RTS_LINKER_USE_MMAP ++#define RTS_LINKER_USE_MMAP_SYMBOLS \ ++ SymI_HasProto(allocateWrite) \ ++ SymI_HasProto(freeWrite) \ ++ SymI_HasProto(markExec) ++#else ++#define RTS_LINKER_USE_MMAP_SYMBOLS /* empty */ ++#endif ++ + #define RTS_SYMBOLS \ + Maybe_Stable_Names \ + RTS_TICKY_SYMBOLS \ + RTS_PROF_SYMBOLS \ + RTS_LIBDW_SYMBOLS \ ++ RTS_LINKER_USE_MMAP_SYMBOLS \ + SymI_HasProto(StgReturn) \ + SymI_HasProto(stg_gc_noregs) \ + SymI_HasProto(stg_ret_v_info) \ +-- +GitLab + diff --git a/buildpath-abi-stability.patch b/buildpath-abi-stability.patch index 1d45c72..7eeee00 100644 --- a/buildpath-abi-stability.patch +++ b/buildpath-abi-stability.patch @@ -1,8 +1,10 @@ Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 ---- a/compiler/iface/MkIface.hs -+++ b/compiler/iface/MkIface.hs -@@ -681,7 +681,7 @@ addFingerprints hsc_env mb_old_fingerpri +Index: ghc-8.10.1/compiler/iface/MkIface.hs +=================================================================== +--- ghc-8.10.1.orig/compiler/iface/MkIface.hs ++++ ghc-8.10.1/compiler/iface/MkIface.hs +@@ -679,7 +679,7 @@ iface_hash <- computeFingerprint putNameLiterally (mod_hash, ann_fn (mkVarOcc "module"), -- See mkIfaceAnnCache @@ -11,9 +13,9 @@ Forwarded to https://ghc.haskell.org/trac/ghc/ticket/10424 sorted_deps, mi_hpc iface0) -@@ -714,6 +714,9 @@ addFingerprints hsc_env mb_old_fingerpri +@@ -714,6 +714,9 @@ + (non_orph_rules, orph_rules) = mkOrphMap ifRuleOrph (mi_rules iface0) (non_orph_fis, orph_fis) = mkOrphMap ifFamInstOrph (mi_fam_insts iface0) - fix_fn = mi_fix_fn iface0 ann_fn = mkIfaceAnnCache (mi_anns iface0) + -- Do not allow filenames to affect the interface + usages = [ case u of UsageFile _ fp -> UsageFile "" fp; _ -> u | u <- mi_usages iface0 ] diff --git a/ghc.spec b/ghc.spec index b1b1eb3..bbdc06d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.13.0.0 +%global base_ver 4.14.2.0 # build profiling libraries # build haddock @@ -37,19 +37,19 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.8 needs llvm-7.0 -%global llvm_major 7.0 +# 8.10.5 can use llvm 9-12 +%global llvm_major 11 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} riscv64 Name: ghc -Version: 8.8.4 +Version: 8.10.5 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 111%{?dist} +Release: 112%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -68,8 +68,11 @@ Patch2: ghc-Cabal-install-PATH-warning.patch Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch +# https://gitlab.haskell.org/ghc/ghc/-/issues/19763 +# https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5915 +Patch7: https://gitlab.haskell.org/ghc/ghc/-/commit/296f25fa5f0fce033b529547e0658076e26f4cda.patch # https://bugzilla.redhat.com/show_bug.cgi?id=1977317 -Patch7: ghc-userguide-sphinx4.patch +Patch8: ghc-userguide-sphinx4.patch # Arch dependent patches @@ -93,19 +96,19 @@ Patch18: Disable-unboxed-arrays.patch # Debian patches: Patch24: buildpath-abi-stability.patch Patch26: no-missing-haddock-file-warning.patch -Patch28: x32-use-native-x86_64-insn.patch +#Patch28: x32-use-native-x86_64-insn.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel # see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros -BuildRequires: ghc-compiler > 8.4 +BuildRequires: ghc-compiler > 8.6 # for ABI hash checking %if %{with abicheck} BuildRequires: ghc %endif -BuildRequires: ghc-rpm-macros-extra >= 2.0.6 +BuildRequires: ghc-rpm-macros-extra BuildRequires: ghc-binary-devel BuildRequires: ghc-bytestring-devel BuildRequires: ghc-containers-devel @@ -239,41 +242,42 @@ This package provides the User Guide and Haddock manual. # use "./libraries-versions.sh" to check versions %if %{defined ghclibdir} -%ghc_lib_subpackage -d -l BSD Cabal-3.0.1.0 +%ghc_lib_subpackage -d -l BSD Cabal-3.2.1.0 %ghc_lib_subpackage -d -l %BSDHaskellReport array-0.5.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} -%ghc_lib_subpackage -d -l BSD binary-0.8.7.0 -%ghc_lib_subpackage -d -l BSD bytestring-0.10.10.1 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.2.1 +%ghc_lib_subpackage -d -l BSD binary-0.8.8.0 +%ghc_lib_subpackage -d -l BSD bytestring-0.10.12.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.4.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport exceptions-0.10.4 %ghc_lib_subpackage -d -l BSD filepath-1.4.2.1 +# in ghc not ghc-libraries: +%ghc_lib_subpackage -d -x ghc-%{ghc_version_override} +%ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-boot-th-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD ghc-compact-0.1.0.0 %ghc_lib_subpackage -d -l BSD ghc-heap-%{ghc_version_override} # see below for ghc-prim -%ghc_lib_subpackage -d -l BSD haskeline-0.7.5.0 -%ghc_lib_subpackage -d -l BSD hpc-0.6.0.3 +%ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} +%ghc_lib_subpackage -d -l BSD haskeline-0.8.0.1 +%ghc_lib_subpackage -d -l BSD hpc-0.6.1.0 # see below for integer-gmp %ghc_lib_subpackage -d -l %BSDHaskellReport libiserv-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD mtl-2.2.2 %ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 %ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.9.0 -%ghc_lib_subpackage -d -l BSD stm-2.5.0.0 -%ghc_lib_subpackage -d -l BSD template-haskell-2.15.0.0 +%ghc_lib_subpackage -d -l BSD stm-2.5.0.1 +%ghc_lib_subpackage -d -l BSD template-haskell-2.16.0.0 %ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 -%ghc_lib_subpackage -d -l BSD text-1.2.4.0 +%ghc_lib_subpackage -d -l BSD text-1.2.4.1 %ghc_lib_subpackage -d -l BSD time-1.9.3 %ghc_lib_subpackage -d -l BSD transformers-0.5.6.2 %ghc_lib_subpackage -d -l BSD unix-2.7.2.2 %if %{with haddock} %ghc_lib_subpackage -d -l BSD xhtml-3000.2.2.1 %endif -# in ghc not ghc-devel: -%ghc_lib_subpackage -d -x ghc-%{ghc_version_override} -%ghc_lib_subpackage -d -x -l BSD ghc-boot-%{ghc_version_override} -%ghc_lib_subpackage -d -x -l BSD ghci-%{ghc_version_override} %endif %global version %{ghc_version_override} @@ -315,6 +319,7 @@ packages to be automatically installed too. %patch2 -p1 -b .orig %patch6 -p1 -b .orig %patch7 -p1 -b .orig +%patch8 -p1 -b .orig rm -r libffi-tarballs @@ -335,7 +340,7 @@ rm -r libffi-tarballs # debian %patch24 -p1 -b .orig %patch26 -p1 -b .orig -%patch28 -p1 -b .orig +#%%patch28 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{with haddock} @@ -448,8 +453,8 @@ echo "%{ghclibdir}/include" >> ghc-base-devel.files %ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} -%ghc_gen_filelists ghc-prim 0.5.3 -%ghc_gen_filelists integer-gmp 1.0.2.0 +%ghc_gen_filelists ghc-prim 0.6.1 +%ghc_gen_filelists integer-gmp 1.0.3.0 %define merge_filelist()\ cp -p libraries/%1/LICENSE libraries/LICENSE.%1\ @@ -566,7 +571,7 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %files compiler %license LICENSE -%doc ANNOUNCE +%doc README.md %{_bindir}/ghc %{_bindir}/ghc-%{version} %{_bindir}/ghc-pkg @@ -590,9 +595,6 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %{ghclibdir}/bin/ghc-iserv-prof %endif %{ghclibdir}/bin/runghc -%ifnarch %{ghc_unregisterized_arches} -%{ghclibdir}/bin/ghc-split -%endif %{ghclibdir}/bin/hp2ps %{ghclibdir}/bin/unlit %{ghclibdir}/ghc-usage.txt @@ -624,6 +626,7 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %ghost %{ghc_html_dir}/libraries/index*.html %ghost %{ghc_html_dir}/libraries/linuwial.css %ghost %{ghc_html_dir}/libraries/minus.gif +%ghost %{ghc_html_dir}/libraries/new-ocean.css %ghost %{ghc_html_dir}/libraries/ocean.css %ghost %{ghc_html_dir}/libraries/plus.gif %ghost %{ghc_html_dir}/libraries/quick-jump.css @@ -658,6 +661,10 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Sun Jul 11 2021 Jens Petersen - 8.10.5-112 +- rebase to 8.10.5 from ghc:8.10 module stream +- https://downloads.haskell.org/~ghc/8.10.5/docs/html/users_guide/8.10.1-notes.html + * Wed Jun 30 2021 Jens Petersen - 8.8.4-111 - fix build with sphinx4 (#1977317) diff --git a/sources b/sources index 579d80e..b5e2cf4 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -SHA512 (ghc-8.8.4-src.tar.xz.sig) = 1ed2e64e8b75a147d7c66b0018119f54ac740131b6f74612aa975c9120d8f7a8a2286829cef22ef2cd16262af0604659daa41c09ef3bdec6c22b8d086fbc1166 -SHA512 (ghc-8.8.4-src.tar.xz) = efd23bd819f7429486696a3a929a040471db7ea8a2d1f1d832e4cf0825b9e1e0c5e6ecad0ab8376f58b74e9c28c1d2f773bd126596d6d853c9e57d57e5ceb090 +SHA512 (ghc-8.10.5-src.tar.xz.sig) = c9d1abf8f4065c1935be877b4978638130307afbfef988ac16d7c972e502b71056a5e5acc1b54b903d8f939a0f2e3ec4ad953cdc7a9ce21024f398ce84cfb2da +SHA512 (ghc-8.10.5-src.tar.xz) = b5f39be0accd5c1cecf1cc326ba3142f561d2ac93e9abf366fe46307d7c0712aac244836e659e1a4d9d0fb98299ea96edc8e8a06f3a81b528b14914b94057ffe From 33e19124c931d684f1beab6e8b20f2b42dbd705f Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Sun, 11 Jul 2021 23:24:28 +0800 Subject: [PATCH 519/530] remove the debian x32 patch --- ghc.spec | 2 -- x32-use-native-x86_64-insn.patch | 27 --------------------------- 2 files changed, 29 deletions(-) delete mode 100644 x32-use-native-x86_64-insn.patch diff --git a/ghc.spec b/ghc.spec index bbdc06d..e50d960 100644 --- a/ghc.spec +++ b/ghc.spec @@ -96,7 +96,6 @@ Patch18: Disable-unboxed-arrays.patch # Debian patches: Patch24: buildpath-abi-stability.patch Patch26: no-missing-haddock-file-warning.patch -#Patch28: x32-use-native-x86_64-insn.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 @@ -340,7 +339,6 @@ rm -r libffi-tarballs # debian %patch24 -p1 -b .orig %patch26 -p1 -b .orig -#%%patch28 -p1 -b .orig %global gen_contents_index gen_contents_index.orig %if %{with haddock} diff --git a/x32-use-native-x86_64-insn.patch b/x32-use-native-x86_64-insn.patch deleted file mode 100644 index 6105b5b..0000000 --- a/x32-use-native-x86_64-insn.patch +++ /dev/null @@ -1,27 +0,0 @@ -Description: Use native x86_64 instructions on x32 - This patch enables a few native 64-bit integer instructions - on x32 which are available on this architecture despite using - 32-bit pointers. These instructions are present on x86_64 but - not on x86 and ghc checks the size of (void *) to determine - that. This method fails on x32 since despite using 32-bit - pointers and hence sizeof(void *) == 4, it still uses the - full x86_64 instruction set and software-emulated variants - of the aforementioned 64-bit integer instructions are - therefore not present in the toolchain which will make ghc - fail to build on x32. - See: https://ghc.haskell.org/trac/ghc/ticket/11571 - . - -Index: ghc-8.0.2/rts/RtsSymbols.c -=================================================================== ---- ghc-8.0.2.orig/rts/RtsSymbols.c -+++ ghc-8.0.2/rts/RtsSymbols.c -@@ -857,7 +857,7 @@ - - - // 64-bit support functions in libgcc.a --#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) -+#if defined(__GNUC__) && SIZEOF_VOID_P <= 4 && !defined(_ABIN32) && !(defined(__x86_64__) && defined(__ILP32__)) - #define RTS_LIBGCC_SYMBOLS \ - SymI_NeedsProto(__divdi3) \ - SymI_NeedsProto(__udivdi3) \ From 2c7a3255ac4820a72806405fa993e1865d17a289 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 12 Jul 2021 01:11:07 +0800 Subject: [PATCH 520/530] enable quick build for s390x llvm bootstrap --- ghc.spec | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index e50d960..4afea93 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,6 +1,6 @@ # disable prof, docs, perf build, debuginfo # NB This must be disabled (bcond_with) for all koji production builds -%bcond_with quickbuild +%bcond_without quickbuild # make sure ghc libraries' ABI hashes unchanged %bcond_without abicheck From bb36bff0b3012b3661f8e25cb58c277cd23d76c1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 12 Jul 2021 10:26:19 +0800 Subject: [PATCH 521/530] enable llvm for s390x --- ghc.spec | 14 +++++++++----- 1 file changed, 9 insertions(+), 5 deletions(-) diff --git a/ghc.spec b/ghc.spec index 4afea93..836bc18 100644 --- a/ghc.spec +++ b/ghc.spec @@ -39,9 +39,9 @@ # 8.10.5 can use llvm 9-12 %global llvm_major 11 -%global ghc_llvm_archs armv7hl aarch64 +%global ghc_llvm_archs armv7hl aarch64 s390x -%global ghc_unregisterized_arches s390 s390x %{mips} riscv64 +%global ghc_unregisterized_arches s390 %{mips} riscv64 Name: ghc Version: 8.10.5 @@ -49,7 +49,7 @@ Version: 8.10.5 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 112%{?dist} +Release: 113%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -79,7 +79,7 @@ Patch8: ghc-userguide-sphinx4.patch # arm Patch12: ghc-armv7-VFPv3D16--NEON.patch -# for unregisterized (s390x) +# for unregisterized # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch Patch16: fix-build-using-unregisterised-v8.6.patch @@ -326,7 +326,8 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif -%ifarch %{ghc_unregisterized_arches} +# remove s390x after switching to llvm +%ifarch %{ghc_unregisterized_arches} s390x %patch15 -p1 -b .orig %patch16 -p1 -b .orig %endif @@ -659,6 +660,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Mon Jul 12 2021 Jens Petersen - 8.10.5-113 +- enable llvm for s390x + * Sun Jul 11 2021 Jens Petersen - 8.10.5-112 - rebase to 8.10.5 from ghc:8.10 module stream - https://downloads.haskell.org/~ghc/8.10.5/docs/html/users_guide/8.10.1-notes.html From 14e83352e8a6c73f378f7b128b492edacb09cd37 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2021 20:16:05 +0800 Subject: [PATCH 522/530] revert to ghc-8.10.4 (since ghc-8.10.5 fails to rebuild on s390x) --- .gitignore | 1 + fix-build-using-unregisterised-v8.6.patch | 31 --------------- ghc-8.10-llvm10.patch | 11 ++++++ ghc.spec | 47 +++++++++++------------ sources | 4 +- 5 files changed, 36 insertions(+), 58 deletions(-) delete mode 100644 fix-build-using-unregisterised-v8.6.patch create mode 100644 ghc-8.10-llvm10.patch diff --git a/.gitignore b/.gitignore index 22069ca..0a57be4 100644 --- a/.gitignore +++ b/.gitignore @@ -33,3 +33,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.8.4-src.tar.xz /ghc-8.10.5-src.tar.xz.sig /ghc-8.10.5-src.tar.xz +/ghc-8.10.4-src.tar.xz.sig diff --git a/fix-build-using-unregisterised-v8.6.patch b/fix-build-using-unregisterised-v8.6.patch deleted file mode 100644 index 3147c68..0000000 --- a/fix-build-using-unregisterised-v8.6.patch +++ /dev/null @@ -1,31 +0,0 @@ -Description: Allow unregisterised ghc-8.6 to build newer GHC - Commit af9b744bbf1 introduced a regression stopping existing unregisterised - compilers from being able to compile newer versions of GHC. The problem is - that the bootstrap compiler uses the newer `includes/stg/MiscClosures.h` file - where some defines have been renamed, resulting in the following error: -. - error: ‘stg_atomicModifyMutVarzh’ undeclared (first use in this function); did you mean ‘stg_atomicModifyMutVar2zh’? -. - For more information, see https://gitlab.haskell.org/ghc/ghc/issues/17111. -. - This patch can be removed, once ghc-8.6 is no longer the bootstrap compiler. -Author: Ilias Tsitsimpis -Bug: https://gitlab.haskell.org/ghc/ghc/issues/17111 - -Index: b/includes/stg/MiscClosures.h -=================================================================== ---- a/includes/stg/MiscClosures.h -+++ b/includes/stg/MiscClosures.h -@@ -390,8 +390,12 @@ RTS_FUN_DECL(stg_copySmallMutableArrayzh - RTS_FUN_DECL(stg_casSmallArrayzh); - - RTS_FUN_DECL(stg_newMutVarzh); -+#if __GLASGOW_HASKELL__ < 808 -+RTS_FUN_DECL(stg_atomicModifyMutVarzh); -+#else - RTS_FUN_DECL(stg_atomicModifyMutVar2zh); - RTS_FUN_DECL(stg_atomicModifyMutVarzuzh); -+#endif - RTS_FUN_DECL(stg_casMutVarzh); - - RTS_FUN_DECL(stg_isEmptyMVarzh); diff --git a/ghc-8.10-llvm10.patch b/ghc-8.10-llvm10.patch new file mode 100644 index 0000000..6996779 --- /dev/null +++ b/ghc-8.10-llvm10.patch @@ -0,0 +1,11 @@ +--- ghc-8.10.2/configure.ac~ 2020-08-04 05:51:52.000000000 +0800 ++++ ghc-8.10.2/configure.ac 2020-08-11 18:57:45.074836178 +0800 +@@ -673,7 +673,7 @@ + # tools we are looking for. In the past, GHC supported a number of + # versions of LLVM simultaneously, but that stopped working around + # 3.5/3.6 release of LLVM. +-LlvmVersion=9 ++LlvmVersion=10 + AC_SUBST([LlvmVersion]) + sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') + AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) diff --git a/ghc.spec b/ghc.spec index 836bc18..836e80d 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.14.2.0 +%global base_ver 4.14.1.0 # build profiling libraries # build haddock @@ -37,14 +37,14 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.10.5 can use llvm 9-12 -%global llvm_major 11 -%global ghc_llvm_archs armv7hl aarch64 s390x +# 8.10 recommends llvm-9 but 10 or even 11 should work +%global llvm_major 10 +%global ghc_llvm_archs armv7hl aarch64 -%global ghc_unregisterized_arches s390 %{mips} riscv64 +%global ghc_unregisterized_arches s390 %{mips} riscv64 s390x Name: ghc -Version: 8.10.5 +Version: 8.10.4 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) @@ -68,21 +68,17 @@ Patch2: ghc-Cabal-install-PATH-warning.patch Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch -# https://gitlab.haskell.org/ghc/ghc/-/issues/19763 -# https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5915 -Patch7: https://gitlab.haskell.org/ghc/ghc/-/commit/296f25fa5f0fce033b529547e0658076e26f4cda.patch # https://bugzilla.redhat.com/show_bug.cgi?id=1977317 Patch8: ghc-userguide-sphinx4.patch # Arch dependent patches - # arm Patch12: ghc-armv7-VFPv3D16--NEON.patch +Patch13: ghc-8.10-llvm10.patch # for unregisterized # https://ghc.haskell.org/trac/ghc/ticket/15689 Patch15: ghc-warnings.mk-CC-Wall.patch -Patch16: fix-build-using-unregisterised-v8.6.patch # bigendian (s390x and ppc64) # https://gitlab.haskell.org/ghc/ghc/issues/15411 @@ -117,6 +113,7 @@ BuildRequires: ghc-process-devel BuildRequires: ghc-transformers-devel BuildRequires: alex BuildRequires: gmp-devel +BuildRequires: hscolour BuildRequires: libffi-devel BuildRequires: make # for terminfo @@ -134,8 +131,8 @@ BuildRequires: llvm%{llvm_major} %if %{with dwarf} BuildRequires: elfutils-devel %endif -%ifarch armv7hl -# patch12 +%ifarch armv7hl %{ghc_llvm_archs} +# patch12, patch13 BuildRequires: autoconf, automake %endif %if %{without quickbuild} @@ -246,7 +243,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %ghc_lib_subpackage -d -l BSD binary-0.8.8.0 %ghc_lib_subpackage -d -l BSD bytestring-0.10.12.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.4.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.2.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 %ghc_lib_subpackage -d -l %BSDHaskellReport exceptions-0.10.4 @@ -267,7 +264,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 %ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.9.0 -%ghc_lib_subpackage -d -l BSD stm-2.5.0.1 +%ghc_lib_subpackage -d -l BSD stm-2.5.0.0 %ghc_lib_subpackage -d -l BSD template-haskell-2.16.0.0 %ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 %ghc_lib_subpackage -d -l BSD text-1.2.4.1 @@ -317,7 +314,6 @@ packages to be automatically installed too. %patch2 -p1 -b .orig %patch6 -p1 -b .orig -%patch7 -p1 -b .orig %patch8 -p1 -b .orig rm -r libffi-tarballs @@ -326,10 +322,13 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif +%ifarch %{ghc_llvm_archs} +%patch13 -p1 -b .orig13 +%endif + # remove s390x after switching to llvm %ifarch %{ghc_unregisterized_arches} s390x %patch15 -p1 -b .orig -%patch16 -p1 -b .orig %endif # bigendian @@ -386,8 +385,8 @@ BUILD_SPHINX_PDF = NO EOF %build -# for patch12 -%ifarch armv7hl +# for patch12 and patch13 +%ifarch armv7hl %{ghc_llvm_archs} autoreconf %endif @@ -660,12 +659,10 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog -* Mon Jul 12 2021 Jens Petersen - 8.10.5-113 -- enable llvm for s390x - -* Sun Jul 11 2021 Jens Petersen - 8.10.5-112 -- rebase to 8.10.5 from ghc:8.10 module stream -- https://downloads.haskell.org/~ghc/8.10.5/docs/html/users_guide/8.10.1-notes.html +* Thu Jul 15 2021 Jens Petersen - 8.10.4-113 +- rebase to 8.10.4 from ghc:8.10 module stream +- https://downloads.haskell.org/ghc/8.10.4/docs/html/users_guide/8.10.1-notes.html +- use llvm10 for ARM * Wed Jun 30 2021 Jens Petersen - 8.8.4-111 - fix build with sphinx4 (#1977317) diff --git a/sources b/sources index b5e2cf4..88bc235 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -SHA512 (ghc-8.10.5-src.tar.xz.sig) = c9d1abf8f4065c1935be877b4978638130307afbfef988ac16d7c972e502b71056a5e5acc1b54b903d8f939a0f2e3ec4ad953cdc7a9ce21024f398ce84cfb2da -SHA512 (ghc-8.10.5-src.tar.xz) = b5f39be0accd5c1cecf1cc326ba3142f561d2ac93e9abf366fe46307d7c0712aac244836e659e1a4d9d0fb98299ea96edc8e8a06f3a81b528b14914b94057ffe +SHA512 (ghc-8.10.4-src.tar.xz) = 9bb078cb72535a352243b83b671c871392564efd09e478549f27ae58fc6f46e337a0782f5500d26d5704ad96eace22e77bb36031a1fe9b7e175f265b0b9c028b +SHA512 (ghc-8.10.4-src.tar.xz.sig) = af7dea2adfe120fb35aba203381062c0d6bb0fd76e675ed016019014954a82a58e1a8509b523ffc826ab4ca717a4e00d30280ac9bc1b2e120af6aecbb314897b From 732b00835c1a8ca969412e7e51c78f6b4b93a1a1 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2021 20:17:29 +0800 Subject: [PATCH 523/530] remove old unused patches --- ...25fa5f0fce033b529547e0658076e26f4cda.patch | 39 --- ...1d895dda4600a85e01c72ff219474b5c7190.patch | 277 ------------------ fix-build-using-unregisterized-v8.2.patch | 51 ---- fix-build-using-unregisterized-v8.4.patch | 58 ---- 4 files changed, 425 deletions(-) delete mode 100644 296f25fa5f0fce033b529547e0658076e26f4cda.patch delete mode 100644 6e361d895dda4600a85e01c72ff219474b5c7190.patch delete mode 100644 fix-build-using-unregisterized-v8.2.patch delete mode 100644 fix-build-using-unregisterized-v8.4.patch diff --git a/296f25fa5f0fce033b529547e0658076e26f4cda.patch b/296f25fa5f0fce033b529547e0658076e26f4cda.patch deleted file mode 100644 index 813c500..0000000 --- a/296f25fa5f0fce033b529547e0658076e26f4cda.patch +++ /dev/null @@ -1,39 +0,0 @@ -From 296f25fa5f0fce033b529547e0658076e26f4cda Mon Sep 17 00:00:00 2001 -From: Adam Sandberg Ericsson -Date: Wed, 28 Apr 2021 20:11:52 +0100 -Subject: [PATCH] rts: export allocateWrite, freeWrite and markExec #19763 - -(cherry picked from commit 2d2985a79eec3d6ae9aee96b264c97c2b158f196) ---- - rts/RtsSymbols.c | 10 ++++++++++ - 1 file changed, 10 insertions(+) - -diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c -index 9ca696c27c4..d5b8cc5fece 100644 ---- a/rts/RtsSymbols.c -+++ b/rts/RtsSymbols.c -@@ -539,11 +539,21 @@ - #define RTS_PROF_SYMBOLS /* empty */ - #endif - -+#if RTS_LINKER_USE_MMAP -+#define RTS_LINKER_USE_MMAP_SYMBOLS \ -+ SymI_HasProto(allocateWrite) \ -+ SymI_HasProto(freeWrite) \ -+ SymI_HasProto(markExec) -+#else -+#define RTS_LINKER_USE_MMAP_SYMBOLS /* empty */ -+#endif -+ - #define RTS_SYMBOLS \ - Maybe_Stable_Names \ - RTS_TICKY_SYMBOLS \ - RTS_PROF_SYMBOLS \ - RTS_LIBDW_SYMBOLS \ -+ RTS_LINKER_USE_MMAP_SYMBOLS \ - SymI_HasProto(StgReturn) \ - SymI_HasProto(stg_gc_noregs) \ - SymI_HasProto(stg_ret_v_info) \ --- -GitLab - diff --git a/6e361d895dda4600a85e01c72ff219474b5c7190.patch b/6e361d895dda4600a85e01c72ff219474b5c7190.patch deleted file mode 100644 index 9f2e86a..0000000 --- a/6e361d895dda4600a85e01c72ff219474b5c7190.patch +++ /dev/null @@ -1,277 +0,0 @@ -From 6e361d895dda4600a85e01c72ff219474b5c7190 Mon Sep 17 00:00:00 2001 -From: Kavon Farvardin -Date: Thu, 4 Oct 2018 13:44:55 -0400 -Subject: [PATCH] Multiple fixes / improvements for LLVM backend - -- Fix for #13904 -- stop "trashing" callee-saved registers, since it is - not actually doing anything useful. - -- Fix for #14251 -- fixes the calling convention for functions passing - raw SSE-register values by adding padding as needed to get the values - in the right registers. This problem cropped up when some args were - unused an dropped from the live list. - -- Fixed a typo in 'readnone' attribute - -- Added 'lower-expect' pass to level 0 LLVM optimization passes to - improve block layout in LLVM for stack checks, etc. - -Test Plan: `make test WAYS=optllvm` and `make test WAYS=llvm` - -Reviewers: bgamari, simonmar, angerman - -Reviewed By: angerman - -Subscribers: rwbarton, carter - -GHC Trac Issues: #13904, #14251 - -Differential Revision: https://phabricator.haskell.org/D5190 - -(cherry picked from commit adcb5fb47c0942671d409b940d8884daa9359ca4) ---- - compiler/llvmGen/Llvm/Types.hs | 2 +- - compiler/llvmGen/LlvmCodeGen/Base.hs | 62 ++++++++++++++++++++---- - compiler/llvmGen/LlvmCodeGen/CodeGen.hs | 59 +++++----------------- - compiler/main/DriverPipeline.hs | 2 +- - testsuite/tests/codeGen/should_run/all.T | 4 +- - 5 files changed, 67 insertions(+), 62 deletions(-) - -diff --git a/compiler/llvmGen/Llvm/Types.hs b/compiler/llvmGen/Llvm/Types.hs -index 87111499fc0..c1c51afcf0f 100644 ---- a/compiler/llvmGen/Llvm/Types.hs -+++ b/compiler/llvmGen/Llvm/Types.hs -@@ -560,7 +560,7 @@ instance Outputable LlvmFuncAttr where - ppr OptSize = text "optsize" - ppr NoReturn = text "noreturn" - ppr NoUnwind = text "nounwind" -- ppr ReadNone = text "readnon" -+ ppr ReadNone = text "readnone" - ppr ReadOnly = text "readonly" - ppr Ssp = text "ssp" - ppr SspReq = text "ssqreq" -diff --git a/compiler/llvmGen/LlvmCodeGen/Base.hs b/compiler/llvmGen/LlvmCodeGen/Base.hs -index 6e20da48c1b..ec91bacc4c8 100644 ---- a/compiler/llvmGen/LlvmCodeGen/Base.hs -+++ b/compiler/llvmGen/LlvmCodeGen/Base.hs -@@ -26,7 +26,7 @@ module LlvmCodeGen.Base ( - - cmmToLlvmType, widthToLlvmFloat, widthToLlvmInt, llvmFunTy, - llvmFunSig, llvmFunArgs, llvmStdFunAttrs, llvmFunAlign, llvmInfAlign, -- llvmPtrBits, tysToParams, llvmFunSection, -+ llvmPtrBits, tysToParams, llvmFunSection, padLiveArgs, isSSE, - - strCLabel_llvm, strDisplayName_llvm, strProcedureName_llvm, - getGlobalPtr, generateExternDecls, -@@ -58,6 +58,8 @@ import ErrUtils - import qualified Stream - - import Control.Monad (ap) -+import Data.List (sort) -+import Data.Maybe (mapMaybe) - - -- ---------------------------------------------------------------------------- - -- * Some Data Types -@@ -147,16 +149,58 @@ llvmFunSection dflags lbl - -- | A Function's arguments - llvmFunArgs :: DynFlags -> LiveGlobalRegs -> [LlvmVar] - llvmFunArgs dflags live = -- map (lmGlobalRegArg dflags) (filter isPassed (activeStgRegs platform)) -+ map (lmGlobalRegArg dflags) (filter isPassed allRegs) - where platform = targetPlatform dflags -- isLive r = not (isSSE r) || r `elem` alwaysLive || r `elem` live -+ allRegs = activeStgRegs platform -+ paddedLive = map (\(_,r) -> r) $ padLiveArgs live -+ isLive r = r `elem` alwaysLive || r `elem` paddedLive - isPassed r = not (isSSE r) || isLive r -- isSSE (FloatReg _) = True -- isSSE (DoubleReg _) = True -- isSSE (XmmReg _) = True -- isSSE (YmmReg _) = True -- isSSE (ZmmReg _) = True -- isSSE _ = False -+ -+ -+isSSE :: GlobalReg -> Bool -+isSSE (FloatReg _) = True -+isSSE (DoubleReg _) = True -+isSSE (XmmReg _) = True -+isSSE (YmmReg _) = True -+isSSE (ZmmReg _) = True -+isSSE _ = False -+ -+sseRegNum :: GlobalReg -> Maybe Int -+sseRegNum (FloatReg i) = Just i -+sseRegNum (DoubleReg i) = Just i -+sseRegNum (XmmReg i) = Just i -+sseRegNum (YmmReg i) = Just i -+sseRegNum (ZmmReg i) = Just i -+sseRegNum _ = Nothing -+ -+-- the bool indicates whether the global reg was added as padding. -+-- the returned list is not sorted in any particular order, -+-- but does indicate the set of live registers needed, with SSE padding. -+padLiveArgs :: LiveGlobalRegs -> [(Bool, GlobalReg)] -+padLiveArgs live = allRegs -+ where -+ sseRegNums = sort $ mapMaybe sseRegNum live -+ (_, padding) = foldl assignSlots (1, []) $ sseRegNums -+ allRegs = padding ++ map (\r -> (False, r)) live -+ -+ assignSlots (i, acc) regNum -+ | i == regNum = -- don't need padding here -+ (i+1, acc) -+ | i < regNum = let -- add padding for slots i .. regNum-1 -+ numNeeded = regNum-i -+ acc' = genPad i numNeeded ++ acc -+ in -+ (regNum+1, acc') -+ | otherwise = error "padLiveArgs -- i > regNum ??" -+ -+ genPad start n = -+ take n $ flip map (iterate (+1) start) (\i -> -+ (True, FloatReg i)) -+ -- NOTE: Picking float should be fine for the following reasons: -+ -- (1) Float aliases with all the other SSE register types on -+ -- the given platform. -+ -- (2) The argument is not live anyways. -+ - - -- | Llvm standard fun attributes - llvmStdFunAttrs :: [LlvmFuncAttr] -diff --git a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs -index e812dd445f1..a7121b7909a 100644 ---- a/compiler/llvmGen/LlvmCodeGen/CodeGen.hs -+++ b/compiler/llvmGen/LlvmCodeGen/CodeGen.hs -@@ -14,7 +14,7 @@ import LlvmCodeGen.Base - import LlvmCodeGen.Regs - - import BlockId --import CodeGen.Platform ( activeStgRegs, callerSaves ) -+import CodeGen.Platform ( activeStgRegs ) - import CLabel - import Cmm - import PprCmm -@@ -211,7 +211,6 @@ genCall t@(PrimTarget (MO_Prefetch_Data localityInt)) [] args - fptr <- liftExprData $ getFunPtr funTy t - argVars' <- castVarsW Signed $ zip argVars argTy - -- doTrashStmts - let argSuffix = [mkIntLit i32 0, mkIntLit i32 localityInt, mkIntLit i32 1] - statement $ Expr $ Call StdCall fptr (argVars' ++ argSuffix) [] - | otherwise = panic $ "prefetch locality level integer must be between 0 and 3, given: " ++ (show localityInt) -@@ -294,7 +293,6 @@ genCall t@(PrimTarget op) [] args - fptr <- getFunPtrW funTy t - argVars' <- castVarsW Signed $ zip argVars argTy - -- doTrashStmts - let alignVal = mkIntLit i32 align - arguments = argVars' ++ (alignVal:isVolVal) - statement $ Expr $ Call StdCall fptr arguments [] -@@ -446,7 +444,6 @@ genCall target res args = runStmtsDecls $ do - | never_returns = statement $ Unreachable - | otherwise = return () - -- doTrashStmts - - -- make the actual call - case retTy of -@@ -1759,12 +1756,9 @@ genLit _ CmmHighStackMark - funPrologue :: LiveGlobalRegs -> [CmmBlock] -> LlvmM StmtData - funPrologue live cmmBlocks = do - -- trash <- getTrashRegs - let getAssignedRegs :: CmmNode O O -> [CmmReg] - getAssignedRegs (CmmAssign reg _) = [reg] -- -- Calls will trash all registers. Unfortunately, this needs them to -- -- be stack-allocated in the first place. -- getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmGlobal trash ++ map CmmLocal rs -+ getAssignedRegs (CmmUnsafeForeignCall _ rs _) = map CmmLocal rs - getAssignedRegs _ = [] - getRegsBlock (_, body, _) = concatMap getAssignedRegs $ blockToList body - assignedRegs = nub $ concatMap (getRegsBlock . blockSplit) cmmBlocks -@@ -1794,14 +1788,9 @@ funPrologue live cmmBlocks = do - funEpilogue :: LiveGlobalRegs -> LlvmM ([LlvmVar], LlvmStatements) - funEpilogue live = do - -- -- Have information and liveness optimisation is enabled? -- let liveRegs = alwaysLive ++ live -- isSSE (FloatReg _) = True -- isSSE (DoubleReg _) = True -- isSSE (XmmReg _) = True -- isSSE (YmmReg _) = True -- isSSE (ZmmReg _) = True -- isSSE _ = False -+ -- the bool indicates whether the register is padding. -+ let alwaysNeeded = map (\r -> (False, r)) alwaysLive -+ livePadded = alwaysNeeded ++ padLiveArgs live - - -- Set to value or "undef" depending on whether the register is - -- actually live -@@ -1813,39 +1802,17 @@ funEpilogue live = do - let ty = (pLower . getVarType $ lmGlobalRegVar dflags r) - return (Just $ LMLitVar $ LMUndefLit ty, nilOL) - platform <- getDynFlag targetPlatform -- loads <- flip mapM (activeStgRegs platform) $ \r -> case () of -- _ | r `elem` liveRegs -> loadExpr r -- | not (isSSE r) -> loadUndef r -+ let allRegs = activeStgRegs platform -+ loads <- flip mapM allRegs $ \r -> case () of -+ _ | (False, r) `elem` livePadded -+ -> loadExpr r -- if r is not padding, load it -+ | not (isSSE r) || (True, r) `elem` livePadded -+ -> loadUndef r - | otherwise -> return (Nothing, nilOL) - - let (vars, stmts) = unzip loads - return (catMaybes vars, concatOL stmts) - -- ---- | A series of statements to trash all the STG registers. ---- ---- In LLVM we pass the STG registers around everywhere in function calls. ---- So this means LLVM considers them live across the entire function, when ---- in reality they usually aren't. For Caller save registers across C calls ---- the saving and restoring of them is done by the Cmm code generator, ---- using Cmm local vars. So to stop LLVM saving them as well (and saving ---- all of them since it thinks they're always live, we trash them just ---- before the call by assigning the 'undef' value to them. The ones we ---- need are restored from the Cmm local var and the ones we don't need ---- are fine to be trashed. --getTrashStmts :: LlvmM LlvmStatements --getTrashStmts = do -- regs <- getTrashRegs -- stmts <- flip mapM regs $ \ r -> do -- reg <- getCmmReg (CmmGlobal r) -- let ty = (pLower . getVarType) reg -- return $ Store (LMLitVar $ LMUndefLit ty) reg -- return $ toOL stmts -- --getTrashRegs :: LlvmM [GlobalReg] --getTrashRegs = do plat <- getLlvmPlatform -- return $ filter (callerSaves plat) (activeStgRegs plat) -- - -- | Get a function pointer to the CLabel specified. - -- - -- This is for Haskell functions, function type is assumed, so doesn't work -@@ -1967,7 +1934,3 @@ getCmmRegW = lift . getCmmReg - genLoadW :: Atomic -> CmmExpr -> CmmType -> WriterT LlvmAccum LlvmM LlvmVar - genLoadW atomic e ty = liftExprData $ genLoad atomic e ty - --doTrashStmts :: WriterT LlvmAccum LlvmM () --doTrashStmts = do -- stmts <- lift getTrashStmts -- tell $ LlvmAccum stmts mempty -diff --git a/compiler/main/DriverPipeline.hs b/compiler/main/DriverPipeline.hs -index 86dd913461c..f4d5e7f553c 100644 ---- a/compiler/main/DriverPipeline.hs -+++ b/compiler/main/DriverPipeline.hs -@@ -1465,7 +1465,7 @@ runPhase (RealPhase LlvmOpt) input_fn dflags - -- we always (unless -optlo specified) run Opt since we rely on it to - -- fix up some pretty big deficiencies in the code we generate - llvmOpts = case optLevel dflags of -- 0 -> "-mem2reg -globalopt" -+ 0 -> "-mem2reg -globalopt -lower-expect" - 1 -> "-O1 -globalopt" - _ -> "-O2" - diff --git a/fix-build-using-unregisterized-v8.2.patch b/fix-build-using-unregisterized-v8.2.patch deleted file mode 100644 index 29d7b49..0000000 --- a/fix-build-using-unregisterized-v8.2.patch +++ /dev/null @@ -1,51 +0,0 @@ -Description: Allow unregisterised ghc-8.2 to build newer GHC - Commit b68697e579d38ca29c2b84377dc2affa04659a28 introduced a regression - stopping existing unregisteristed compilers from being used to compile a newer - version of GHC. The problem is that the bootstrap compiler uses the newer Stg.h - where EB_, IB_, etc, definitions have changed resulting in the following error: -. - error: conflicting types for 'ghc_GhcPrelude_zdtrModule4_bytes' - note: in definition of macro 'EB_' - #define EB_(X) extern const char X[] - note: previous definition of 'ghc_GhcPrelude_zdtrModule4_bytes' was here - char ghc_GhcPrelude_zdtrModule4_bytes[] = "ghc"; -. - For more information about the problem, see https://phabricator.haskell.org/D4114. -. - This patch is a rework of https://phabricator.haskell.org/D3741. - It modifies Stg.h to include the old definitions, if a compiler older than - 8.4 is being used. -. - This patch can be removed, once ghc-8.2 is no longer the bootstrap compiler. -Author: Ilias Tsitsimpis -Bug: https://ghc.haskell.org/trac/ghc/ticket/15201 - -Index: b/includes/Stg.h -=================================================================== ---- a/includes/Stg.h -+++ b/includes/Stg.h -@@ -232,6 +232,16 @@ typedef StgInt I_; - typedef StgWord StgWordArray[]; - typedef StgFunPtr F_; - -+#if __GLASGOW_HASKELL__ < 804 -+#define EB_(X) extern char X[] -+#define IB_(X) static char X[] -+#define EI_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) -+#define II_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8)) -+#define IF_(f) static StgFunPtr GNUC3_ATTRIBUTE(used) f(void) -+#define FN_(f) StgFunPtr f(void) -+#define EF_(f) StgFunPtr f(void) /* External Cmm functions */ -+#define EFF_(f) void f() /* See Note [External function prototypes] */ -+#else - /* byte arrays (and strings): */ - #define EB_(X) extern const char X[] - #define IB_(X) static const char X[] -@@ -250,6 +260,7 @@ typedef StgFunPtr F_; - #define EF_(f) StgFunPtr f(void) /* External Cmm functions */ - /* foreign functions: */ - #define EFF_(f) void f() /* See Note [External function prototypes] */ -+#endif /* __GLASGOW_HASKELL__ < 804 */ - - /* Note [External function prototypes] See Trac #8965, #11395 - ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ diff --git a/fix-build-using-unregisterized-v8.4.patch b/fix-build-using-unregisterized-v8.4.patch deleted file mode 100644 index c524733..0000000 --- a/fix-build-using-unregisterized-v8.4.patch +++ /dev/null @@ -1,58 +0,0 @@ -Description: Allow unregisterised ghc-8.4 to build newer GHC - Commit 4075656e8bb introduced a regression stopping existing unregisteristed - compilers from being able to compile newer versions of GHC. The problem is - that the bootstrap compiler uses the newer `rts/storage/ClosureTypes.h` file - where some defines have been renamed, resulting in the following error: -. - error: ‘stg_MUT_ARR_PTRS_FROZEN0_info’ undeclared (first use in this function); did you mean ‘stg_MUT_ARR_PTRS_FROZEN_DIRTY_info’? -. - For more information, see https://gitlab.haskell.org/ghc/ghc/issues/15913. -. - This patch can be removed, once ghc-8.4 is no longer the bootstrap compiler. -Author: Ilias Tsitsimpis -Bug: https://gitlab.haskell.org/ghc/ghc/issues/15913 -Bug-Debian: https://bugs.debian.org/932941 - -Index: b/includes/rts/storage/ClosureTypes.h -=================================================================== ---- a/includes/rts/storage/ClosureTypes.h -+++ b/includes/rts/storage/ClosureTypes.h -@@ -82,5 +82,11 @@ - #define SMALL_MUT_ARR_PTRS_DIRTY 60 - #define SMALL_MUT_ARR_PTRS_FROZEN_DIRTY 61 - #define SMALL_MUT_ARR_PTRS_FROZEN_CLEAN 62 -+#if __GLASGOW_HASKELL__ < 806 -+#define SMALL_MUT_ARR_PTRS_FROZEN0 SMALL_MUT_ARR_PTRS_FROZEN_DIRTY -+#define SMALL_MUT_ARR_PTRS_FROZEN SMALL_MUT_ARR_PTRS_FROZEN_CLEAN -+#define MUT_ARR_PTRS_FROZEN0 MUT_ARR_PTRS_FROZEN_DIRTY -+#define MUT_ARR_PTRS_FROZEN MUT_ARR_PTRS_FROZEN_CLEAN -+#endif - #define COMPACT_NFDATA 63 - #define N_CLOSURE_TYPES 64 -Index: b/includes/stg/MiscClosures.h -=================================================================== ---- a/includes/stg/MiscClosures.h -+++ b/includes/stg/MiscClosures.h -@@ -116,12 +116,22 @@ RTS_ENTRY(stg_ARR_WORDS); - RTS_ENTRY(stg_MUT_ARR_WORDS); - RTS_ENTRY(stg_MUT_ARR_PTRS_CLEAN); - RTS_ENTRY(stg_MUT_ARR_PTRS_DIRTY); -+#if __GLASGOW_HASKELL__ < 806 -+RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN); -+RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN0); -+#else - RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN_CLEAN); - RTS_ENTRY(stg_MUT_ARR_PTRS_FROZEN_DIRTY); -+#endif - RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_CLEAN); - RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_DIRTY); -+#if __GLASGOW_HASKELL__ < 806 -+RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN); -+RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN0); -+#else - RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN_CLEAN); - RTS_ENTRY(stg_SMALL_MUT_ARR_PTRS_FROZEN_DIRTY); -+#endif - RTS_ENTRY(stg_MUT_VAR_CLEAN); - RTS_ENTRY(stg_MUT_VAR_DIRTY); - RTS_ENTRY(stg_END_TSO_QUEUE); From 64fe442db9c9c86fdaba88caf912248cb0bcfc90 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 15 Jul 2021 23:27:17 +0800 Subject: [PATCH 524/530] enable llvm backend for s390x and perf build --- ghc.spec | 11 +++++++---- 1 file changed, 7 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 836e80d..178fa2e 100644 --- a/ghc.spec +++ b/ghc.spec @@ -1,6 +1,6 @@ # disable prof, docs, perf build, debuginfo # NB This must be disabled (bcond_with) for all koji production builds -%bcond_without quickbuild +%bcond_with quickbuild # make sure ghc libraries' ABI hashes unchanged %bcond_without abicheck @@ -39,9 +39,9 @@ # 8.10 recommends llvm-9 but 10 or even 11 should work %global llvm_major 10 -%global ghc_llvm_archs armv7hl aarch64 +%global ghc_llvm_archs armv7hl aarch64 s390x -%global ghc_unregisterized_arches s390 %{mips} riscv64 s390x +%global ghc_unregisterized_arches s390 %{mips} riscv64 Name: ghc Version: 8.10.4 @@ -49,7 +49,7 @@ Version: 8.10.4 # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 113%{?dist} +Release: 114%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -659,6 +659,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Thu Jul 15 2021 Jens Petersen - 8.10.4-114 +- enable llvm backend for s390x + * Thu Jul 15 2021 Jens Petersen - 8.10.4-113 - rebase to 8.10.4 from ghc:8.10 module stream - https://downloads.haskell.org/ghc/8.10.4/docs/html/users_guide/8.10.1-notes.html From 91fb67816db1167ab7201d8f2e14c420b4060afa Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Mon, 19 Jul 2021 19:53:53 +0800 Subject: [PATCH 525/530] turn off llvm for s390x again https://gitlab.haskell.org/ghc/ghc/-/issues/20120 --- ghc.spec | 8 ++++---- 1 file changed, 4 insertions(+), 4 deletions(-) diff --git a/ghc.spec b/ghc.spec index 178fa2e..67e7ed6 100644 --- a/ghc.spec +++ b/ghc.spec @@ -39,9 +39,9 @@ # 8.10 recommends llvm-9 but 10 or even 11 should work %global llvm_major 10 -%global ghc_llvm_archs armv7hl aarch64 s390x +%global ghc_llvm_archs armv7hl aarch64 -%global ghc_unregisterized_arches s390 %{mips} riscv64 +%global ghc_unregisterized_arches s390 %{mips} riscv64 s390x Name: ghc Version: 8.10.4 @@ -139,8 +139,8 @@ BuildRequires: autoconf, automake #BuildRequires: gnupg2 %endif Requires: ghc-compiler = %{version}-%{release} -Requires: ghc-ghc-devel = %{version}-%{release} Requires: ghc-devel = %{version}-%{release} +Requires: ghc-ghc-devel = %{version}-%{release} %if %{with haddock} Suggests: ghc-doc = %{version}-%{release} Suggests: ghc-doc-index = %{version}-%{release} @@ -660,7 +660,7 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog * Thu Jul 15 2021 Jens Petersen - 8.10.4-114 -- enable llvm backend for s390x +- perf build * Thu Jul 15 2021 Jens Petersen - 8.10.4-113 - rebase to 8.10.4 from ghc:8.10 module stream From 86b21a1199f018f7d464b64057a952a1cf4d7058 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 21 Jul 2021 20:22:00 +0800 Subject: [PATCH 526/530] opt-out of F35 mass rebuild with noautobuild --- noautobuild | 0 1 file changed, 0 insertions(+), 0 deletions(-) create mode 100644 noautobuild diff --git a/noautobuild b/noautobuild new file mode 100644 index 0000000..e69de29 From 23a07931cff11450d27cd15efc5c9f1b068feed8 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Thu, 22 Jul 2021 23:13:50 +0800 Subject: [PATCH 527/530] revert back to 8.10.5 with rts patch and without s390x llvm reduce cpus for post %install scripts for armv7hl --- ...25fa5f0fce033b529547e0658076e26f4cda.patch | 39 ++++++++++++++++ ghc-8.10-llvm10.patch | 11 ----- ghc.spec | 44 ++++++++++++------- sources | 4 +- 4 files changed, 68 insertions(+), 30 deletions(-) create mode 100644 296f25fa5f0fce033b529547e0658076e26f4cda.patch delete mode 100644 ghc-8.10-llvm10.patch diff --git a/296f25fa5f0fce033b529547e0658076e26f4cda.patch b/296f25fa5f0fce033b529547e0658076e26f4cda.patch new file mode 100644 index 0000000..813c500 --- /dev/null +++ b/296f25fa5f0fce033b529547e0658076e26f4cda.patch @@ -0,0 +1,39 @@ +From 296f25fa5f0fce033b529547e0658076e26f4cda Mon Sep 17 00:00:00 2001 +From: Adam Sandberg Ericsson +Date: Wed, 28 Apr 2021 20:11:52 +0100 +Subject: [PATCH] rts: export allocateWrite, freeWrite and markExec #19763 + +(cherry picked from commit 2d2985a79eec3d6ae9aee96b264c97c2b158f196) +--- + rts/RtsSymbols.c | 10 ++++++++++ + 1 file changed, 10 insertions(+) + +diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c +index 9ca696c27c4..d5b8cc5fece 100644 +--- a/rts/RtsSymbols.c ++++ b/rts/RtsSymbols.c +@@ -539,11 +539,21 @@ + #define RTS_PROF_SYMBOLS /* empty */ + #endif + ++#if RTS_LINKER_USE_MMAP ++#define RTS_LINKER_USE_MMAP_SYMBOLS \ ++ SymI_HasProto(allocateWrite) \ ++ SymI_HasProto(freeWrite) \ ++ SymI_HasProto(markExec) ++#else ++#define RTS_LINKER_USE_MMAP_SYMBOLS /* empty */ ++#endif ++ + #define RTS_SYMBOLS \ + Maybe_Stable_Names \ + RTS_TICKY_SYMBOLS \ + RTS_PROF_SYMBOLS \ + RTS_LIBDW_SYMBOLS \ ++ RTS_LINKER_USE_MMAP_SYMBOLS \ + SymI_HasProto(StgReturn) \ + SymI_HasProto(stg_gc_noregs) \ + SymI_HasProto(stg_ret_v_info) \ +-- +GitLab + diff --git a/ghc-8.10-llvm10.patch b/ghc-8.10-llvm10.patch deleted file mode 100644 index 6996779..0000000 --- a/ghc-8.10-llvm10.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-8.10.2/configure.ac~ 2020-08-04 05:51:52.000000000 +0800 -+++ ghc-8.10.2/configure.ac 2020-08-11 18:57:45.074836178 +0800 -@@ -673,7 +673,7 @@ - # tools we are looking for. In the past, GHC supported a number of - # versions of LLVM simultaneously, but that stopped working around - # 3.5/3.6 release of LLVM. --LlvmVersion=9 -+LlvmVersion=10 - AC_SUBST([LlvmVersion]) - sUPPORTED_LLVM_VERSION=$(echo \($LlvmVersion\) | sed 's/\./,/') - AC_DEFINE_UNQUOTED([sUPPORTED_LLVM_VERSION], ${sUPPORTED_LLVM_VERSION}, [The supported LLVM version number]) diff --git a/ghc.spec b/ghc.spec index 67e7ed6..041ec66 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.14.1.0 +%global base_ver 4.14.2.0 # build profiling libraries # build haddock @@ -19,6 +19,7 @@ %bcond_with perf_build %undefine _enable_debug_packages %else +%bcond_without ghc_prof %bcond_without haddock %bcond_without perf_build %endif @@ -37,19 +38,19 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.10 recommends llvm-9 but 10 or even 11 should work -%global llvm_major 10 +# 8.10.5 can use llvm 9-12 +%global llvm_major 11 %global ghc_llvm_archs armv7hl aarch64 -%global ghc_unregisterized_arches s390 %{mips} riscv64 s390x +%global ghc_unregisterized_arches s390 s390x %{mips} riscv64 Name: ghc -Version: 8.10.4 +Version: 8.10.5 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 114%{?dist} +Release: 115%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -68,13 +69,15 @@ Patch2: ghc-Cabal-install-PATH-warning.patch Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch +# https://gitlab.haskell.org/ghc/ghc/-/issues/19763 +# https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5915 +Patch7: https://gitlab.haskell.org/ghc/ghc/-/commit/296f25fa5f0fce033b529547e0658076e26f4cda.patch # https://bugzilla.redhat.com/show_bug.cgi?id=1977317 Patch8: ghc-userguide-sphinx4.patch # Arch dependent patches # arm Patch12: ghc-armv7-VFPv3D16--NEON.patch -Patch13: ghc-8.10-llvm10.patch # for unregisterized # https://ghc.haskell.org/trac/ghc/ticket/15689 @@ -131,8 +134,8 @@ BuildRequires: llvm%{llvm_major} %if %{with dwarf} BuildRequires: elfutils-devel %endif -%ifarch armv7hl %{ghc_llvm_archs} -# patch12, patch13 +%ifarch armv7hl +# patch12 BuildRequires: autoconf, automake %endif %if %{without quickbuild} @@ -243,7 +246,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %ghc_lib_subpackage -d -l BSD binary-0.8.8.0 %ghc_lib_subpackage -d -l BSD bytestring-0.10.12.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.2.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.4.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 %ghc_lib_subpackage -d -l %BSDHaskellReport exceptions-0.10.4 @@ -264,7 +267,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 %ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.9.0 -%ghc_lib_subpackage -d -l BSD stm-2.5.0.0 +%ghc_lib_subpackage -d -l BSD stm-2.5.0.1 %ghc_lib_subpackage -d -l BSD template-haskell-2.16.0.0 %ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 %ghc_lib_subpackage -d -l BSD text-1.2.4.1 @@ -314,6 +317,7 @@ packages to be automatically installed too. %patch2 -p1 -b .orig %patch6 -p1 -b .orig +%patch7 -p1 -b .orig %patch8 -p1 -b .orig rm -r libffi-tarballs @@ -322,10 +326,6 @@ rm -r libffi-tarballs %patch12 -p1 -b .orig %endif -%ifarch %{ghc_llvm_archs} -%patch13 -p1 -b .orig13 -%endif - # remove s390x after switching to llvm %ifarch %{ghc_unregisterized_arches} s390x %patch15 -p1 -b .orig @@ -385,8 +385,8 @@ BUILD_SPHINX_PDF = NO EOF %build -# for patch12 and patch13 -%ifarch armv7hl %{ghc_llvm_archs} +# for patch12 +%ifarch armv7hl autoreconf %endif @@ -488,6 +488,11 @@ install -p -m 0644 %{SOURCE5} %{buildroot}%{_mandir}/man1/ghc-pkg.1 install -p -m 0644 %{SOURCE6} %{buildroot}%{_mandir}/man1/haddock.1 install -p -m 0644 %{SOURCE7} %{buildroot}%{_mandir}/man1/runghc.1 +%ifarch armv7hl +export RPM_BUILD_NCPUS=1 +%endif + + %check export LANG=en_US.utf8 # stolen from ghc6/debian/rules: @@ -659,6 +664,11 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Thu Jul 22 2021 Jens Petersen - 8.10.5-115 +- update to 8.10.5 with patch for missing rts symbols +- use llvm 11 for ARM +- https://downloads.haskell.org/~ghc/8.10.5/docs/html/users_guide/8.10.5-notes.html + * Thu Jul 15 2021 Jens Petersen - 8.10.4-114 - perf build diff --git a/sources b/sources index 88bc235..b5e2cf4 100644 --- a/sources +++ b/sources @@ -1,2 +1,2 @@ -SHA512 (ghc-8.10.4-src.tar.xz) = 9bb078cb72535a352243b83b671c871392564efd09e478549f27ae58fc6f46e337a0782f5500d26d5704ad96eace22e77bb36031a1fe9b7e175f265b0b9c028b -SHA512 (ghc-8.10.4-src.tar.xz.sig) = af7dea2adfe120fb35aba203381062c0d6bb0fd76e675ed016019014954a82a58e1a8509b523ffc826ab4ca717a4e00d30280ac9bc1b2e120af6aecbb314897b +SHA512 (ghc-8.10.5-src.tar.xz.sig) = c9d1abf8f4065c1935be877b4978638130307afbfef988ac16d7c972e502b71056a5e5acc1b54b903d8f939a0f2e3ec4ad953cdc7a9ce21024f398ce84cfb2da +SHA512 (ghc-8.10.5-src.tar.xz) = b5f39be0accd5c1cecf1cc326ba3142f561d2ac93e9abf366fe46307d7c0712aac244836e659e1a4d9d0fb98299ea96edc8e8a06f3a81b528b14914b94057ffe From 6a9ed335cb07e5dc7ec87c32a05ad6170d44188b Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Wed, 4 Aug 2021 23:50:04 +0800 Subject: [PATCH 528/530] Revert "opt-out of F35 mass rebuild with noautobuild" This reverts commit 0c5dec5b3cbc69fb88f2951270c228d21a13df16. --- noautobuild | 0 1 file changed, 0 insertions(+), 0 deletions(-) delete mode 100644 noautobuild diff --git a/noautobuild b/noautobuild deleted file mode 100644 index e69de29..0000000 From 0937c78f4186d6638ba478b7b03f7fe615901614 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Fri, 17 Sep 2021 18:49:45 +0800 Subject: [PATCH 529/530] move zlib-devel Recommends to cabal-install --- ghc.spec | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/ghc.spec b/ghc.spec index 041ec66..fe9a119 100644 --- a/ghc.spec +++ b/ghc.spec @@ -154,7 +154,6 @@ Suggests: ghc-manual = %{version}-%{release} %if %{with ghc_prof} Suggests: ghc-prof = %{version}-%{release} %endif -Recommends: zlib-devel %description GHC is a state-of-the-art, open source, compiler and interactive environment @@ -664,6 +663,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Fri Sep 17 2021 Jens Petersen +- move zlib-devel Recommends to cabal-install + * Thu Jul 22 2021 Jens Petersen - 8.10.5-115 - update to 8.10.5 with patch for missing rts symbols - use llvm 11 for ARM From 3aa816c924e53791cca88c295d632a71b934cb39 Mon Sep 17 00:00:00 2001 From: Jens Petersen Date: Tue, 29 Mar 2022 12:57:25 +0800 Subject: [PATCH 530/530] update to 8.10.7 --- .gitignore | 1 + ...25fa5f0fce033b529547e0658076e26f4cda.patch | 39 ----------- ghc-userguide-sphinx4.patch | 11 ---- ghc.spec | 65 ++++++------------- sources | 3 +- 5 files changed, 23 insertions(+), 96 deletions(-) delete mode 100644 296f25fa5f0fce033b529547e0658076e26f4cda.patch delete mode 100644 ghc-userguide-sphinx4.patch diff --git a/.gitignore b/.gitignore index 0a57be4..21e8e7b 100644 --- a/.gitignore +++ b/.gitignore @@ -34,3 +34,4 @@ testsuite-6.12.3.tar.bz2 /ghc-8.10.5-src.tar.xz.sig /ghc-8.10.5-src.tar.xz /ghc-8.10.4-src.tar.xz.sig +/ghc-8.10.7-src.tar.xz diff --git a/296f25fa5f0fce033b529547e0658076e26f4cda.patch b/296f25fa5f0fce033b529547e0658076e26f4cda.patch deleted file mode 100644 index 813c500..0000000 --- a/296f25fa5f0fce033b529547e0658076e26f4cda.patch +++ /dev/null @@ -1,39 +0,0 @@ -From 296f25fa5f0fce033b529547e0658076e26f4cda Mon Sep 17 00:00:00 2001 -From: Adam Sandberg Ericsson -Date: Wed, 28 Apr 2021 20:11:52 +0100 -Subject: [PATCH] rts: export allocateWrite, freeWrite and markExec #19763 - -(cherry picked from commit 2d2985a79eec3d6ae9aee96b264c97c2b158f196) ---- - rts/RtsSymbols.c | 10 ++++++++++ - 1 file changed, 10 insertions(+) - -diff --git a/rts/RtsSymbols.c b/rts/RtsSymbols.c -index 9ca696c27c4..d5b8cc5fece 100644 ---- a/rts/RtsSymbols.c -+++ b/rts/RtsSymbols.c -@@ -539,11 +539,21 @@ - #define RTS_PROF_SYMBOLS /* empty */ - #endif - -+#if RTS_LINKER_USE_MMAP -+#define RTS_LINKER_USE_MMAP_SYMBOLS \ -+ SymI_HasProto(allocateWrite) \ -+ SymI_HasProto(freeWrite) \ -+ SymI_HasProto(markExec) -+#else -+#define RTS_LINKER_USE_MMAP_SYMBOLS /* empty */ -+#endif -+ - #define RTS_SYMBOLS \ - Maybe_Stable_Names \ - RTS_TICKY_SYMBOLS \ - RTS_PROF_SYMBOLS \ - RTS_LIBDW_SYMBOLS \ -+ RTS_LINKER_USE_MMAP_SYMBOLS \ - SymI_HasProto(StgReturn) \ - SymI_HasProto(stg_gc_noregs) \ - SymI_HasProto(stg_ret_v_info) \ --- -GitLab - diff --git a/ghc-userguide-sphinx4.patch b/ghc-userguide-sphinx4.patch deleted file mode 100644 index 8c31df1..0000000 --- a/ghc-userguide-sphinx4.patch +++ /dev/null @@ -1,11 +0,0 @@ ---- ghc-8.8.4/docs/users_guide/conf.py~ 2020-07-09 00:43:03.000000000 +0800 -+++ ghc-8.8.4/docs/users_guide/conf.py 2021-07-01 00:09:03.537324304 +0800 -@@ -77,7 +77,7 @@ - latex_elements = { - 'inputenc': '', - 'utf8extra': '', -- 'preamble': ''' -+ 'preamble': r''' - \usepackage{fontspec} - \usepackage{makeidx} - \setsansfont{DejaVu Sans} diff --git a/ghc.spec b/ghc.spec index fe9a119..41311ac 100644 --- a/ghc.spec +++ b/ghc.spec @@ -8,7 +8,7 @@ # to handle RCs %global ghc_release %{version} -%global base_ver 4.14.2.0 +%global base_ver 4.14.3.0 # build profiling libraries # build haddock @@ -24,12 +24,6 @@ %bcond_without perf_build %endif -# to enable dwarf info (only on intel archs): overrides perf -# default is off: bcond_with -%ifarch x86_64 i686 -%bcond_with dwarf -%endif - # locked together since disabling haddock causes no manuals built # and disabling haddock still created index.html # https://ghc.haskell.org/trac/ghc/ticket/15190 @@ -38,19 +32,19 @@ # no longer build testsuite (takes time and not really being used) %bcond_with testsuite -# 8.10.5 can use llvm 9-12 +# 8.10 can use llvm 9-12 %global llvm_major 11 %global ghc_llvm_archs armv7hl aarch64 %global ghc_unregisterized_arches s390 s390x %{mips} riscv64 Name: ghc -Version: 8.10.5 +Version: 8.10.7 # Since library subpackages are versioned: # - release can only be reset if *all* library versions get bumped simultaneously # (sometimes after a major release) # - minor release numbers for a branch should be incremented monotonically -Release: 115%{?dist} +Release: 116%{?dist} Summary: Glasgow Haskell Compiler License: BSD and HaskellReport @@ -59,7 +53,6 @@ Source0: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-src.tar %if %{with testsuite} Source1: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-testsuite.tar.xz %endif -Source2: https://downloads.haskell.org/ghc/%{ghc_release}/ghc-%{version}-src.tar.xz.sig Source5: ghc-pkg.man Source6: haddock.man Source7: runghc.man @@ -69,11 +62,6 @@ Patch2: ghc-Cabal-install-PATH-warning.patch Patch3: ghc-gen_contents_index-nodocs.patch # https://phabricator.haskell.org/rGHC4eebc8016f68719e1ccdf460754a97d1f4d6ef05 Patch6: ghc-8.6.3-sphinx-1.8.patch -# https://gitlab.haskell.org/ghc/ghc/-/issues/19763 -# https://gitlab.haskell.org/ghc/ghc/-/merge_requests/5915 -Patch7: https://gitlab.haskell.org/ghc/ghc/-/commit/296f25fa5f0fce033b529547e0658076e26f4cda.patch -# https://bugzilla.redhat.com/show_bug.cgi?id=1977317 -Patch8: ghc-userguide-sphinx4.patch # Arch dependent patches # arm @@ -99,7 +87,8 @@ Patch26: no-missing-haddock-file-warning.patch # fedora ghc has been bootstrapped on # %%{ix86} x86_64 ppc ppc64 armv7hl s390 s390x ppc64le aarch64 # and retired arches: alpha sparcv9 armv5tel -# see also deprecated ghc_arches defined in /etc/rpm/macros.ghc-srpm by redhat-rpm-macros +# see also deprecated ghc_arches defined in ghc-srpm-macros +# /usr/lib/rpm/macros.d/macros.ghc-srpm BuildRequires: ghc-compiler > 8.6 # for ABI hash checking @@ -113,6 +102,8 @@ BuildRequires: ghc-containers-devel BuildRequires: ghc-directory-devel BuildRequires: ghc-pretty-devel BuildRequires: ghc-process-devel +BuildRequires: ghc-stm-devel +BuildRequires: ghc-template-haskell-devel BuildRequires: ghc-transformers-devel BuildRequires: alex BuildRequires: gmp-devel @@ -131,16 +122,10 @@ BuildRequires: python3-sphinx %ifarch %{ghc_llvm_archs} BuildRequires: llvm%{llvm_major} %endif -%if %{with dwarf} -BuildRequires: elfutils-devel -%endif %ifarch armv7hl # patch12 BuildRequires: autoconf, automake %endif -%if %{without quickbuild} -#BuildRequires: gnupg2 -%endif Requires: ghc-compiler = %{version}-%{release} Requires: ghc-devel = %{version}-%{release} Requires: ghc-ghc-devel = %{version}-%{release} @@ -245,7 +230,7 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l %BSDHaskellReport -c gmp-devel%{?_isa},libffi-devel%{?_isa} base-%{base_ver} %ghc_lib_subpackage -d -l BSD binary-0.8.8.0 %ghc_lib_subpackage -d -l BSD bytestring-0.10.12.0 -%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.4.1 +%ghc_lib_subpackage -d -l %BSDHaskellReport containers-0.6.5.1 %ghc_lib_subpackage -d -l %BSDHaskellReport deepseq-1.4.4.0 %ghc_lib_subpackage -d -l %BSDHaskellReport directory-1.3.6.0 %ghc_lib_subpackage -d -l %BSDHaskellReport exceptions-0.10.4 @@ -258,14 +243,14 @@ This package provides the User Guide and Haddock manual. %ghc_lib_subpackage -d -l BSD ghc-heap-%{ghc_version_override} # see below for ghc-prim %ghc_lib_subpackage -d -l BSD -x ghci-%{ghc_version_override} -%ghc_lib_subpackage -d -l BSD haskeline-0.8.0.1 +%ghc_lib_subpackage -d -l BSD haskeline-0.8.2 %ghc_lib_subpackage -d -l BSD hpc-0.6.1.0 # see below for integer-gmp %ghc_lib_subpackage -d -l %BSDHaskellReport libiserv-%{ghc_version_override} %ghc_lib_subpackage -d -l BSD mtl-2.2.2 %ghc_lib_subpackage -d -l BSD parsec-3.1.14.0 %ghc_lib_subpackage -d -l BSD pretty-1.1.3.6 -%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.9.0 +%ghc_lib_subpackage -d -l %BSDHaskellReport process-1.6.13.2 %ghc_lib_subpackage -d -l BSD stm-2.5.0.1 %ghc_lib_subpackage -d -l BSD template-haskell-2.16.0.0 %ghc_lib_subpackage -d -l BSD -c ncurses-devel%{?_isa} terminfo-0.4.1.4 @@ -306,9 +291,6 @@ packages to be automatically installed too. %prep -%if %{without quickbuild} -#%%{gpgverify} --keyring='%{SOURCE3}' --signature='%{SOURCE2}' --data='%{SOURCE0}' -%endif %setup -q -n %{name}-%{version} %{?with_testsuite:-b1} %patch1 -p1 -b .orig @@ -316,13 +298,11 @@ packages to be automatically installed too. %patch2 -p1 -b .orig %patch6 -p1 -b .orig -%patch7 -p1 -b .orig -%patch8 -p1 -b .orig rm -r libffi-tarballs %ifarch armv7hl -%patch12 -p1 -b .orig +%patch12 -p1 -b .orig12 %endif # remove s390x after switching to llvm @@ -339,8 +319,8 @@ rm -r libffi-tarballs %patch24 -p1 -b .orig %patch26 -p1 -b .orig -%global gen_contents_index gen_contents_index.orig %if %{with haddock} +%global gen_contents_index gen_contents_index.orig if [ ! -f "libraries/%{gen_contents_index}" ]; then echo "Missing libraries/%{gen_contents_index}, needed at end of %%install!" exit 1 @@ -353,12 +333,8 @@ cat > mk/build.mk << EOF %ifarch %{ghc_llvm_archs} BuildFlavour = perf-llvm %else -%if %{with dwarf} -BuildFlavour = dwarf -%else BuildFlavour = perf %endif -%endif %else %ifarch %{ghc_llvm_archs} BuildFlavour = quick-llvm @@ -390,7 +366,6 @@ autoreconf %endif %ghc_set_gcc_flags -# for ghc >= 8.2 export CC=%{_bindir}/gcc # * %%configure induces cross-build due to different target/host/build platform names @@ -404,7 +379,6 @@ export CC=%{_bindir}/gcc %ifarch %{ghc_unregisterized_arches} --enable-unregisterised \ %endif - %{?with_dwarf:--enable-dwarf-unwind} \ %{nil} # avoid "ghc: hGetContents: invalid argument (invalid byte sequence)" @@ -447,8 +421,8 @@ done echo "%%dir %{ghclibdir}" >> ghc-base%{?_ghcdynlibdir:-devel}.files echo "%{ghclibdir}/include" >> ghc-base-devel.files -%ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghc %{ghc_version_override} +%ghc_gen_filelists ghc-boot %{ghc_version_override} %ghc_gen_filelists ghci %{ghc_version_override} %ghc_gen_filelists ghc-prim 0.6.1 %ghc_gen_filelists integer-gmp 1.0.3.0 @@ -461,8 +435,8 @@ for i in devel doc prof; do\ cat ghc-%1-$i.files >> ghc-%2-$i.files\ done -%merge_filelist integer-gmp base %merge_filelist ghc-prim base +%merge_filelist integer-gmp base # add rts libs rm -f rts.files @@ -493,7 +467,7 @@ export RPM_BUILD_NCPUS=1 %check -export LANG=en_US.utf8 +export LANG=C.utf8 # stolen from ghc6/debian/rules: GHC=inplace/bin/ghc-stage2 # Do some very simple tests that the compiler actually works @@ -502,8 +476,6 @@ mkdir testghc echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo [ "$(testghc/foo)" = "Foo" ] -# doesn't seem to work inplace: -#[ "$(inplace/bin/runghc testghc/foo.hs)" = "Foo" ] rm testghc/* echo 'main = putStrLn "Foo"' > testghc/foo.hs $GHC testghc/foo.hs -o testghc/foo -O2 @@ -514,6 +486,8 @@ $GHC testghc/foo.hs -o testghc/foo -dynamic [ "$(testghc/foo)" = "Foo" ] rm testghc/* +$GHC --info + # check the ABI hashes %if %{with abicheck} if [ "%{version}" = "$(ghc --numeric-version)" ]; then @@ -663,6 +637,9 @@ env -C %{ghc_html_libraries_dir} ./gen_contents_index %changelog +* Tue Mar 29 2022 Jens Petersen - 8.10.7-116 +- https://downloads.haskell.org/~ghc/8.10.7/docs/html/users_guide/8.10.7-notes.html + * Fri Sep 17 2021 Jens Petersen - move zlib-devel Recommends to cabal-install diff --git a/sources b/sources index b5e2cf4..6645ec0 100644 --- a/sources +++ b/sources @@ -1,2 +1 @@ -SHA512 (ghc-8.10.5-src.tar.xz.sig) = c9d1abf8f4065c1935be877b4978638130307afbfef988ac16d7c972e502b71056a5e5acc1b54b903d8f939a0f2e3ec4ad953cdc7a9ce21024f398ce84cfb2da -SHA512 (ghc-8.10.5-src.tar.xz) = b5f39be0accd5c1cecf1cc326ba3142f561d2ac93e9abf366fe46307d7c0712aac244836e659e1a4d9d0fb98299ea96edc8e8a06f3a81b528b14914b94057ffe +SHA512 (ghc-8.10.7-src.tar.xz) = eaf35de6da9b196f1e26bbbb681d60e4fe5f94a9e2af265a1ea5b5aef8ad2b10848ff946eb61d128095002624aced52c01c7f8cf1d72fd9120b8cc7762ddc3c3