summaryrefslogtreecommitdiff
path: root/dev-lang/ghc/files
diff options
context:
space:
mode:
Diffstat (limited to 'dev-lang/ghc/files')
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-cgen-constify.patch378
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-ghci-cross.patch60
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-hp2ps-cross.patch104
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-stage2-cross.patch81
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-staged-cross.patch43
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-unphased-cross.patch30
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-1.patch124
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-2-hack.patch144
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc2-O2-unreg.patch35
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc3-any-vendor.patch44
-rw-r--r--dev-lang/ghc/files/ghc-8.2.1_rc3-stginit-data.patch27
11 files changed, 1070 insertions, 0 deletions
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-cgen-constify.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-cgen-constify.patch
new file mode 100644
index 00000000000..2e1ef932b45
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-cgen-constify.patch
@@ -0,0 +1,378 @@
+From 7e00046772e053c63ac93630a60b0f396e32a2d7 Mon Sep 17 00:00:00 2001
+From: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Sun, 16 Apr 2017 10:43:38 +0100
+Subject: [PATCH] compiler/cmm/PprC.hs: constify labels in .rodata
+
+Summary:
+Consider one-line module
+ module B (v) where v = "hello"
+in -fvia-C mode it generates code like
+ static char gibberish_str[] = "hello";
+
+It resides in data section (precious resource on ia64!).
+The patch switches genrator to emit:
+ static const char gibberish_str[] = "hello";
+
+Other types if symbols that gained 'const' qualifier are:
+
+- info tables (from haskell and CMM)
+- static reference tables (from haskell and CMM)
+
+Cleanups along the way:
+
+- fixed info tables defined in .cmm to reside in .rodata
+- split out closure declaration into 'IC_' / 'EC_'
+- added label declaration (based on label type) right before
+ each label definition (based on section type) so that C
+ compiler could check if declaration and definition matches
+ at definition site.
+
+Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+Test Plan: ran testsuite on unregisterised x86_64 compiler
+
+Reviewers: simonmar, ezyang, austin, bgamari, erikd
+
+Subscribers: rwbarton, thomie
+
+GHC Trac Issues: #8996
+
+Differential Revision: https://phabricator.haskell.org/D3481
+---
+ compiler/cmm/CLabel.hs | 24 ++++++++++++++
+ compiler/cmm/Cmm.hs | 13 ++++++++
+ compiler/cmm/CmmInfo.hs | 2 +-
+ compiler/cmm/PprC.hs | 62 +++++++++++++++++++++++-------------
+ compiler/llvmGen/LlvmCodeGen/Data.hs | 12 -------
+ includes/Stg.h | 22 +++++++++----
+ includes/rts/storage/InfoTables.h | 2 +-
+ includes/stg/MiscClosures.h | 14 ++++----
+ 8 files changed, 102 insertions(+), 49 deletions(-)
+
+diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs
+index 3ba4f7647a..62c8037e9c 100644
+--- a/compiler/cmm/CLabel.hs
++++ b/compiler/cmm/CLabel.hs
+@@ -89,6 +89,8 @@ module CLabel (
+ foreignLabelStdcallInfo,
+ isBytesLabel,
+ isForeignLabel,
++ isSomeRODataLabel,
++ isStaticClosureLabel,
+ mkCCLabel, mkCCSLabel,
+
+ DynamicLinkerLabelInfo(..),
+@@ -575,6 +577,28 @@ isForeignLabel :: CLabel -> Bool
+ isForeignLabel (ForeignLabel _ _ _ _) = True
+ isForeignLabel _lbl = False
+
++-- | Whether label is a static closure label (can come from haskell or cmm)
++isStaticClosureLabel :: CLabel -> Bool
++-- Closure defined in haskell (.hs)
++isStaticClosureLabel (IdLabel _ _ Closure) = True
++-- Closure defined in cmm
++isStaticClosureLabel (CmmLabel _ _ CmmClosure) = True
++isStaticClosureLabel _lbl = False
++
++-- | Whether label is a .rodata label
++isSomeRODataLabel :: CLabel -> Bool
++-- info table defined in haskell (.hs)
++isSomeRODataLabel (IdLabel _ _ ClosureTable) = True
++isSomeRODataLabel (IdLabel _ _ ConInfoTable) = True
++isSomeRODataLabel (IdLabel _ _ InfoTable) = True
++isSomeRODataLabel (IdLabel _ _ LocalInfoTable) = True
++-- static reference tables defined in haskell (.hs)
++isSomeRODataLabel (IdLabel _ _ SRT) = True
++isSomeRODataLabel (SRTLabel _) = True
++-- info table defined in cmm (.cmm)
++isSomeRODataLabel (CmmLabel _ _ CmmInfo) = True
++isSomeRODataLabel _lbl = False
++
+ -- | Get the label size field from a ForeignLabel
+ foreignLabelStdcallInfo :: CLabel -> Maybe Int
+ foreignLabelStdcallInfo (ForeignLabel _ info _ _) = info
+diff --git a/compiler/cmm/Cmm.hs b/compiler/cmm/Cmm.hs
+index d2ee531686..bab20f3fdd 100644
+--- a/compiler/cmm/Cmm.hs
++++ b/compiler/cmm/Cmm.hs
+@@ -9,6 +9,7 @@ module Cmm (
+ CmmBlock,
+ RawCmmDecl, RawCmmGroup,
+ Section(..), SectionType(..), CmmStatics(..), CmmStatic(..),
++ isSecConstant,
+
+ -- ** Blocks containing lists
+ GenBasicBlock(..), blockId,
+@@ -167,6 +168,18 @@ data SectionType
+ | OtherSection String
+ deriving (Show)
+
++-- | Should a data in this section be considered constant
++isSecConstant :: Section -> Bool
++isSecConstant (Section t _) = case t of
++ Text -> True
++ ReadOnlyData -> True
++ RelocatableReadOnlyData -> True
++ ReadOnlyData16 -> True
++ CString -> True
++ Data -> False
++ UninitialisedData -> False
++ (OtherSection _) -> False
++
+ data Section = Section SectionType CLabel
+
+ data CmmStatic
+diff --git a/compiler/cmm/CmmInfo.hs b/compiler/cmm/CmmInfo.hs
+index b5e800a977..35e3a1888d 100644
+--- a/compiler/cmm/CmmInfo.hs
++++ b/compiler/cmm/CmmInfo.hs
+@@ -133,7 +133,7 @@ mkInfoTable dflags proc@(CmmProc infos entry_lbl live blocks)
+ --
+ return (top_decls ++
+ [CmmProc mapEmpty entry_lbl live blocks,
+- mkDataLits (Section Data info_lbl) info_lbl
++ mkRODataLits info_lbl
+ (CmmLabel entry_lbl : rel_std_info ++ rel_extra_bits)])
+
+ --
+diff --git a/compiler/cmm/PprC.hs b/compiler/cmm/PprC.hs
+index 56de94079f..21ed6f6516 100644
+--- a/compiler/cmm/PprC.hs
++++ b/compiler/cmm/PprC.hs
+@@ -83,12 +83,13 @@ pprC tops = vcat $ intersperse blankLine $ map pprTop tops
+ -- top level procs
+ --
+ pprTop :: RawCmmDecl -> SDoc
+-pprTop (CmmProc infos clbl _ graph) =
++pprTop (CmmProc infos clbl _in_live_regs graph) =
+
+ (case mapLookup (g_entry graph) infos of
+ Nothing -> empty
+- Just (Statics info_clbl info_dat) -> pprDataExterns info_dat $$
+- pprWordArray info_clbl info_dat) $$
++ Just (Statics info_clbl info_dat) ->
++ pprDataExterns info_dat $$
++ pprWordArray info_is_in_rodata info_clbl info_dat) $$
+ (vcat [
+ blankLine,
+ extern_decls,
+@@ -99,6 +100,8 @@ pprTop (CmmProc infos clbl _ graph) =
+ rbrace ]
+ )
+ where
++ -- info tables are always in .rodata
++ info_is_in_rodata = True
+ blocks = toBlockListEntryFirst graph
+ (temp_decls, extern_decls) = pprTempAndExternDecls blocks
+
+@@ -107,21 +110,23 @@ pprTop (CmmProc infos clbl _ graph) =
+
+ -- We only handle (a) arrays of word-sized things and (b) strings.
+
+-pprTop (CmmData _section (Statics lbl [CmmString str])) =
++pprTop (CmmData section (Statics lbl [CmmString str])) =
++ pprExternDecl lbl $$
+ hcat [
+- pprLocalness lbl, text "char ", ppr lbl,
++ pprLocalness lbl, pprConstness (isSecConstant section), text "char ", ppr lbl,
+ text "[] = ", pprStringInCStyle str, semi
+ ]
+
+-pprTop (CmmData _section (Statics lbl [CmmUninitialised size])) =
++pprTop (CmmData section (Statics lbl [CmmUninitialised size])) =
++ pprExternDecl lbl $$
+ hcat [
+- pprLocalness lbl, text "char ", ppr lbl,
++ pprLocalness lbl, pprConstness (isSecConstant section), text "char ", ppr lbl,
+ brackets (int size), semi
+ ]
+
+-pprTop (CmmData _section (Statics lbl lits)) =
++pprTop (CmmData section (Statics lbl lits)) =
+ pprDataExterns lits $$
+- pprWordArray lbl lits
++ pprWordArray (isSecConstant section) lbl lits
+
+ -- --------------------------------------------------------------------------
+ -- BasicBlocks are self-contained entities: they always end in a jump.
+@@ -141,10 +146,12 @@ pprBBlock block =
+ -- Info tables. Just arrays of words.
+ -- See codeGen/ClosureInfo, and nativeGen/PprMach
+
+-pprWordArray :: CLabel -> [CmmStatic] -> SDoc
+-pprWordArray lbl ds
++pprWordArray :: Bool -> CLabel -> [CmmStatic] -> SDoc
++pprWordArray is_ro lbl ds
+ = sdocWithDynFlags $ \dflags ->
+- hcat [ pprLocalness lbl, text "StgWord"
++ -- TODO: align closures only
++ pprExternDecl lbl $$
++ hcat [ pprLocalness lbl, pprConstness is_ro, text "StgWord"
+ , space, ppr lbl, text "[]"
+ -- See Note [StgWord alignment]
+ , pprAlignment (wordWidth dflags)
+@@ -180,6 +187,10 @@ pprLocalness :: CLabel -> SDoc
+ pprLocalness lbl | not $ externallyVisibleCLabel lbl = text "static "
+ | otherwise = empty
+
++pprConstness :: Bool -> SDoc
++pprConstness is_ro | is_ro = text "const "
++ | otherwise = empty
++
+ -- --------------------------------------------------------------------------
+ -- Statements.
+ --
+@@ -984,31 +995,38 @@ is_cishCC JavaScriptCallConv = False
+ pprTempAndExternDecls :: [CmmBlock] -> (SDoc{-temps-}, SDoc{-externs-})
+ pprTempAndExternDecls stmts
+ = (pprUFM (getUniqSet temps) (vcat . map pprTempDecl),
+- vcat (map (pprExternDecl False{-ToDo-}) (Map.keys lbls)))
++ vcat (map pprExternDecl (Map.keys lbls)))
+ where (temps, lbls) = runTE (mapM_ te_BB stmts)
+
+ pprDataExterns :: [CmmStatic] -> SDoc
+ pprDataExterns statics
+- = vcat (map (pprExternDecl False{-ToDo-}) (Map.keys lbls))
++ = vcat (map pprExternDecl (Map.keys lbls))
+ where (_, lbls) = runTE (mapM_ te_Static statics)
+
+ pprTempDecl :: LocalReg -> SDoc
+ pprTempDecl l@(LocalReg _ rep)
+ = hcat [ machRepCType rep, space, pprLocalReg l, semi ]
+
+-pprExternDecl :: Bool -> CLabel -> SDoc
+-pprExternDecl _in_srt lbl
++pprExternDecl :: CLabel -> SDoc
++pprExternDecl lbl
+ -- do not print anything for "known external" things
+ | not (needsCDecl lbl) = empty
+ | Just sz <- foreignLabelStdcallInfo lbl = stdcall_decl sz
+ | otherwise =
+- hcat [ visibility, label_type lbl,
+- lparen, ppr lbl, text ");" ]
++ hcat [ visibility, label_type lbl , lparen, ppr lbl, text ");"
++ -- occasionally useful to see label type
++ -- , text "/* ", pprDebugCLabel lbl, text " */"
++ ]
+ where
+- label_type lbl | isBytesLabel lbl = text "B_"
+- | isForeignLabel lbl && isCFunctionLabel lbl = text "FF_"
+- | isCFunctionLabel lbl = text "F_"
+- | otherwise = text "I_"
++ label_type lbl | isBytesLabel lbl = text "B_"
++ | isForeignLabel lbl && isCFunctionLabel lbl
++ = text "FF_"
++ | isCFunctionLabel lbl = text "F_"
++ | isStaticClosureLabel lbl = text "C_"
++ -- generic .rodata labels
++ | isSomeRODataLabel lbl = text "RO_"
++ -- generic .data labels (common case)
++ | otherwise = text "RW_"
+
+ visibility
+ | externallyVisibleCLabel lbl = char 'E'
+diff --git a/compiler/llvmGen/LlvmCodeGen/Data.hs b/compiler/llvmGen/LlvmCodeGen/Data.hs
+index 9bb5a75bda..adb86d312d 100644
+--- a/compiler/llvmGen/LlvmCodeGen/Data.hs
++++ b/compiler/llvmGen/LlvmCodeGen/Data.hs
+@@ -56,18 +56,6 @@ genLlvmData (sec, Statics lbl xs) = do
+
+ return ([globDef], [tyAlias])
+
+--- | Should a data in this section be considered constant
+-isSecConstant :: Section -> Bool
+-isSecConstant (Section t _) = case t of
+- Text -> True
+- ReadOnlyData -> True
+- RelocatableReadOnlyData -> True
+- ReadOnlyData16 -> True
+- CString -> True
+- Data -> False
+- UninitialisedData -> False
+- (OtherSection _) -> False
+-
+ -- | Format the section type part of a Cmm Section
+ llvmSectionType :: Platform -> SectionType -> FastString
+ llvmSectionType p t = case t of
+diff --git a/includes/Stg.h b/includes/Stg.h
+index 619984d8e5..b1b3190307 100644
+--- a/includes/Stg.h
++++ b/includes/Stg.h
+@@ -223,13 +223,23 @@ typedef StgInt I_;
+ typedef StgWord StgWordArray[];
+ typedef StgFunPtr F_;
+
+-#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))
++/* byte arrays (and strings): */
++#define EB_(X) extern const char X[]
++#define IB_(X) static const char X[]
++/* static (non-heap) closures (requires alignment for pointer tagging): */
++#define EC_(X) extern StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
++#define IC_(X) static StgWordArray (X) GNU_ATTRIBUTE(aligned (8))
++/* writable data (does not require alignment): */
++#define ERW_(X) extern StgWordArray (X)
++#define IRW_(X) static StgWordArray (X)
++/* read-only data (does not require alignment): */
++#define ERO_(X) extern const StgWordArray (X)
++#define IRO_(X) static const StgWordArray (X)
++/* stg-native functions: */
+ #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 FN_(f) StgFunPtr f(void)
++#define EF_(f) StgFunPtr f(void) /* External Cmm functions */
++/* foreign functions: */
+ #define EFF_(f) void f() /* See Note [External function prototypes] */
+
+ /* Note [External function prototypes] See Trac #8965, #11395
+diff --git a/includes/rts/storage/InfoTables.h b/includes/rts/storage/InfoTables.h
+index 307aac371c..163f1d1c87 100644
+--- a/includes/rts/storage/InfoTables.h
++++ b/includes/rts/storage/InfoTables.h
+@@ -266,7 +266,7 @@ typedef struct {
+ } StgFunInfoTable;
+
+ // canned bitmap for each arg type, indexed by constants in FunTypes.h
+-extern StgWord stg_arg_bitmaps[];
++extern const StgWord stg_arg_bitmaps[];
+
+ /* -----------------------------------------------------------------------------
+ Return info tables
+diff --git a/includes/stg/MiscClosures.h b/includes/stg/MiscClosures.h
+index 9d907ab3ba..b604f1c42b 100644
+--- a/includes/stg/MiscClosures.h
++++ b/includes/stg/MiscClosures.h
+@@ -21,10 +21,10 @@
+ #define STGMISCCLOSURES_H
+
+ #if IN_STG_CODE
+-# define RTS_RET_INFO(i) extern W_(i)[]
+-# define RTS_FUN_INFO(i) extern W_(i)[]
+-# define RTS_THUNK_INFO(i) extern W_(i)[]
+-# define RTS_INFO(i) extern W_(i)[]
++# define RTS_RET_INFO(i) extern const W_(i)[]
++# define RTS_FUN_INFO(i) extern const W_(i)[]
++# define RTS_THUNK_INFO(i) extern const W_(i)[]
++# define RTS_INFO(i) extern const W_(i)[]
+ # define RTS_CLOSURE(i) extern W_(i)[]
+ # define RTS_FUN_DECL(f) extern DLL_IMPORT_RTS StgFunPtr f(void)
+ #else
+@@ -489,9 +489,9 @@ extern StgWord RTS_VAR(sched_mutex);
+
+ // Apply.cmm
+ // canned bitmap for each arg type
+-extern StgWord stg_arg_bitmaps[];
+-extern StgWord stg_ap_stack_entries[];
+-extern StgWord stg_stack_save_entries[];
++extern const StgWord stg_arg_bitmaps[];
++extern const StgWord stg_ap_stack_entries[];
++extern const StgWord stg_stack_save_entries[];
+
+ // Storage.c
+ extern unsigned int RTS_VAR(g0);
+--
+2.12.2
+
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-ghci-cross.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-ghci-cross.patch
new file mode 100644
index 00000000000..dbba18e85c7
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-ghci-cross.patch
@@ -0,0 +1,60 @@
+commit 732b3dbbff194eb8650c75afd79d892801afa0dc
+Author: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Thu Apr 6 22:48:13 2017 +0100
+
+ add $(CrossCompilePrefix) to 'runghc' and 'ghci'
+
+ When Stage1Only=YES install mode is used one of rare tools
+ that lack $(CrossCompilePrefix) prefix are 'runghc' and 'ghci'.
+
+ This causes file collisions when multiple GHC crosscompilers
+ are installed in system.
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+diff --git a/driver/ghci/ghc.mk b/driver/ghci/ghc.mk
+index 41d1f15c17..0f31884080 100644
+--- a/driver/ghci/ghc.mk
++++ b/driver/ghci/ghc.mk
+@@ -16,16 +16,16 @@ ifneq "$(Windows_Host)" "YES"
+ install: install_driver_ghci
+
+ .PHONY: install_driver_ghci
+-install_driver_ghci: WRAPPER=$(DESTDIR)$(bindir)/ghci-$(ProjectVersion)
++install_driver_ghci: WRAPPER=$(DESTDIR)$(bindir)/$(CrossCompilePrefix)ghci-$(ProjectVersion)
+ install_driver_ghci:
+ $(INSTALL_DIR) "$(DESTDIR)$(bindir)"
+ $(call removeFiles, "$(WRAPPER)")
+ $(CREATE_SCRIPT) "$(WRAPPER)"
+ echo '#!$(SHELL)' >> "$(WRAPPER)"
+- echo 'exec "$(bindir)/ghc-$(ProjectVersion)" --interactive "$$@"' >> "$(WRAPPER)"
++ echo 'exec "$(bindir)/$(CrossCompilePrefix)ghc-$(ProjectVersion)" --interactive "$$@"' >> "$(WRAPPER)"
+ $(EXECUTABLE_FILE) "$(WRAPPER)"
+- $(call removeFiles,"$(DESTDIR)$(bindir)/ghci")
+- $(LN_S) ghci-$(ProjectVersion) "$(DESTDIR)$(bindir)/ghci"
++ $(call removeFiles,"$(DESTDIR)$(bindir)/$(CrossCompilePrefix)ghci")
++ $(LN_S) $(CrossCompilePrefix)ghci-$(ProjectVersion) "$(DESTDIR)$(bindir)/$(CrossCompilePrefix)ghci"
+
+ else # Windows_Host...
+
+diff --git a/utils/runghc/ghc.mk b/utils/runghc/ghc.mk
+index 9169ca21bd..50b11a612e 100644
+--- a/utils/runghc/ghc.mk
++++ b/utils/runghc/ghc.mk
+@@ -34,11 +34,11 @@ install: install_runhaskell
+ .PHONY: install_runhaskell
+ ifeq "$(Windows_Host)" "YES"
+ install_runhaskell: install_bins
+- "$(CP)" $(DESTDIR)$(bindir)/runghc$(exeext1) $(DESTDIR)$(bindir)/runhaskell$(exeext1)
++ "$(CP)" $(DESTDIR)$(bindir)/$(CrossCompilePrefix)runghc$(exeext1) $(DESTDIR)$(bindir)/$(CrossCompilePrefix)runhaskell$(exeext1)
+ else
+ install_runhaskell:
+- $(call removeFiles,"$(DESTDIR)$(bindir)/runhaskell")
+- $(LN_S) runghc "$(DESTDIR)$(bindir)/runhaskell"
+- $(call removeFiles,"$(DESTDIR)$(bindir)/runghc")
+- $(LN_S) runghc-$(ProjectVersion) "$(DESTDIR)$(bindir)/runghc"
++ $(call removeFiles,"$(DESTDIR)$(bindir)/$(CrossCompilePrefix)runhaskell")
++ $(LN_S) $(CrossCompilePrefix)runghc "$(DESTDIR)$(bindir)/$(CrossCompilePrefix)runhaskell"
++ $(call removeFiles,"$(DESTDIR)$(bindir)/$(CrossCompilePrefix)runghc")
++ $(LN_S) $(CrossCompilePrefix)runghc-$(ProjectVersion) "$(DESTDIR)$(bindir)/$(CrossCompilePrefix)runghc"
+ endif
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-hp2ps-cross.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-hp2ps-cross.patch
new file mode 100644
index 00000000000..26382b3cf44
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-hp2ps-cross.patch
@@ -0,0 +1,104 @@
+commit ff84d052850b637b03bbb98cf05202e44886257d
+Author: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Sat Apr 8 10:02:34 2017 +0100
+
+ cross-build 'unlit' and 'hp2ps' for stage2 install
+
+ In navive build case it does not matter much if we build
+ 'unlit' and 'hp2ps' tools with ghc-stage0 or ghc-stage1:
+ both GHCs are native compilers and both tools are written
+ in C (have no haskell code).
+
+ But in cross-case the difference is substantial:
+ In Stag1Only=YES case we need to install native tools built
+ by ghc-stage0/${host}-cc.
+ In Stag1Only=NO case we need to install cross-built tools
+ built by ghc-stage1/${target}-cc.
+
+ Before this change GHC did not have a rule to build cross-built
+ 'unlit' and 'hp2ps'.
+
+ The change adds cross-built 'unlit' and 'hp2ps' as 'dist-install'
+ targets.
+
+ 'inplace/lib/bin/unlit.bin' target is unchanged and still contains
+ native binary.
+
+ As a result this change allows cross-building and packaging whole
+ GHC for target platform!
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+diff --git a/utils/hp2ps/ghc.mk b/utils/hp2ps/ghc.mk
+index f6e01ec6c1..21ce87dcfa 100644
+--- a/utils/hp2ps/ghc.mk
++++ b/utils/hp2ps/ghc.mk
+@@ -10,6 +10,7 @@
+ #
+ # -----------------------------------------------------------------------------
+
++# stage0
+ utils/hp2ps_dist_C_SRCS = AreaBelow.c Curves.c Error.c Main.c \
+ Reorder.c TopTwenty.c AuxFile.c Deviation.c \
+ HpFile.c Marks.c Scale.c TraceElement.c \
+@@ -17,11 +18,27 @@ utils/hp2ps_dist_C_SRCS = AreaBelow.c Curves.c Error.c Main.c \
+ Utilities.c
+ utils/hp2ps_dist_EXTRA_LIBRARIES = m
+ utils/hp2ps_dist_PROGNAME = hp2ps
+-utils/hp2ps_dist_INSTALL = YES
+ utils/hp2ps_dist_INSTALL_INPLACE = YES
+ utils/hp2ps_dist_SHELL_WRAPPER = YES
+ utils/hp2ps_dist_INSTALL_SHELL_WRAPPER_NAME = hp2ps
+
+ utils/hp2ps_CC_OPTS += $(addprefix -I,$(GHC_INCLUDE_DIRS))
+
++# stage 1
++utils/hp2ps_dist-install_C_SRCS = $(utils/hp2ps_dist_C_SRCS)
++utils/hp2ps_dist-install_EXTRA_LIBRARIES = $(utils/hp2ps_dist_EXTRA_LIBRARIES)
++utils/hp2ps_dist-install_PROGNAME = $(utils/hp2ps_dist_PROGNAME)
++utils/hp2ps_dist-install_INSTALL_INPLACE = NO
++utils/hp2ps_dist-install_SHELL_WRAPPER = YES
++utils/hp2ps_dist-install_INSTALL_SHELL_WRAPPER_NAME = $(utils/hp2ps_dist_INSTALL_SHELL_WRAPPER_NAME)
++
++ifeq "$(Stage1Only)" "YES"
++utils/hp2ps_dist_INSTALL = YES
++utils/hp2ps_dist-install_INSTALL = NO
++else
++utils/hp2ps_dist_INSTALL = NO
++utils/hp2ps_dist-install_INSTALL = YES
++endif
++
+ $(eval $(call build-prog,utils/hp2ps,dist,0))
++$(eval $(call build-prog,utils/hp2ps,dist-install,1))
+diff --git a/utils/unlit/ghc.mk b/utils/unlit/ghc.mk
+index e947989b5e..8911f4e856 100644
+--- a/utils/unlit/ghc.mk
++++ b/utils/unlit/ghc.mk
+@@ -10,11 +10,25 @@
+ #
+ # -----------------------------------------------------------------------------
+
++# built by ghc-stage0
+ utils/unlit_dist_C_SRCS = unlit.c
+ utils/unlit_dist_PROGNAME = unlit
+ utils/unlit_dist_TOPDIR = YES
+-utils/unlit_dist_INSTALL = YES
+ utils/unlit_dist_INSTALL_INPLACE = YES
+
+-$(eval $(call build-prog,utils/unlit,dist,0))
++# built by ghc-stage1
++utils/unlit_dist-install_C_SRCS = $(utils/unlit_dist_C_SRCS)
++utils/unlit_dist-install_PROGNAME = $(utils/unlit_dist_PROGNAME)
++utils/unlit_dist-install_TOPDIR = $(utils/unlit_dist_TOPDIR)
++utils/unlit_dist-install_INSTALL_INPLACE = NO
++
++ifeq "$(Stage1Only)" "YES"
++utils/unlit_dist_INSTALL = YES
++utils/unlit_dist-install_INSTALL = NO
++else
++utils/unlit_dist_INSTALL = NO
++utils/unlit_dist-install_INSTALL = YES
++endif
+
++$(eval $(call build-prog,utils/unlit,dist,0))
++$(eval $(call build-prog,utils/unlit,dist-install,1))
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-stage2-cross.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-stage2-cross.patch
new file mode 100644
index 00000000000..1439d722fef
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-stage2-cross.patch
@@ -0,0 +1,81 @@
+commit 54895c90440cb81f18657537b91f2aa35bd54173
+Author: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Fri Apr 7 10:08:58 2017 +0100
+
+ fix 'make install' for cross-stage2
+
+ When cross-built GHC is being installed one of
+ latest steps is to register installed libraries
+ with 'ghc-pkg'.
+
+ GHC uses freshly installed 'ghc-pkg' and 'ghc-stage2'
+ for that.
+
+ Tested as:
+ ./configure --target=aarch64-unknown-linux-gnu
+ make install DESTDIR=$(pwd)/__s2 STRIP_CMD=:
+
+ Before the change install failed on ghc-pkg execution phase:
+
+ ".../ghc-cross/__s2/usr/local/lib/ghc-8.3.20170406/bin/ghc-pkg" \
+ --force \
+ --global-package-db \
+ ".../ghc-cross/__s2/usr/local/lib/ghc-8.3.20170406/package.conf.d" \
+ update rts/dist/package.conf.install
+ /bin/sh: .../ghc-cross/__s2/usr/local/lib/ghc-8.3.20170406/bin/ghc-pkg: \
+ No such file or directory
+
+ To avoid breakage we use 'ghc' and 'ghc-pkg' built by stage0.
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+ Test Plan: run 'make install' on stage2 crosscompiler
+
+ Reviewers: rwbarton, austin, bgamari
+
+ Subscribers: thomie, snowleopard
+
+ Differential Revision: https://phabricator.haskell.org/D3432
+
+diff --git a/ghc.mk b/ghc.mk
+index caa6c38fbb..8971f25981 100644
+--- a/ghc.mk
++++ b/ghc.mk
+@@ -962,6 +962,12 @@ endif
+
+ INSTALLED_PACKAGE_CONF=$(DESTDIR)$(topdir)/package.conf.d
+
++ifeq "$(CrossCompiling)" "YES"
++# when installing ghc-stage2 we can't run target's
++# 'ghc-pkg' and 'ghc-stage2' but those are needed for registration.
++INSTALLED_GHC_REAL=$(TOP)/inplace/bin/ghc-stage1
++INSTALLED_GHC_PKG_REAL=$(TOP)/$(ghc-pkg_DIST_BINARY)
++else # CrossCompiling
+ # Install packages in the right order, so that ghc-pkg doesn't complain.
+ # Also, install ghc-pkg first.
+ ifeq "$(Windows_Host)" "NO"
+@@ -971,6 +977,7 @@ else
+ INSTALLED_GHC_REAL=$(DESTDIR)$(bindir)/ghc.exe
+ INSTALLED_GHC_PKG_REAL=$(DESTDIR)$(bindir)/ghc-pkg.exe
+ endif
++endif # CrossCompiling
+
+ # Set the INSTALL_DISTDIR_p for each package; compiler is special
+ $(foreach p,$(filter-out compiler,$(INSTALL_PACKAGES)),\
+diff --git a/utils/ghc-pkg/ghc.mk b/utils/ghc-pkg/ghc.mk
+index 002c8122f2..4d5ef4e108 100644
+--- a/utils/ghc-pkg/ghc.mk
++++ b/utils/ghc-pkg/ghc.mk
+@@ -49,6 +49,12 @@ utils/ghc-pkg_dist_PROGNAME = ghc-pkg
+ utils/ghc-pkg_dist_SHELL_WRAPPER = YES
+ utils/ghc-pkg_dist_INSTALL_INPLACE = YES
+
++# When cross-built ghc-stage2 is installed 'make install' needs to call
++# native ghc-pkg (not the cross-built one) to register installed packages
++# 'ghc-pkg_DIST_BINARY' variable only refer to native binary.
++ghc-pkg_DIST_BINARY_NAME = ghc-pkg$(exeext0)
++ghc-pkg_DIST_BINARY = utils/ghc-pkg/dist/build/tmp/$(ghc-pkg_DIST_BINARY_NAME)
++
+ # See Note [Stage1Only vs stage=1] in mk/config.mk.in.
+ ifeq "$(Stage1Only)" "YES"
+ # Install the copy of ghc-pkg from the dist directory when running 'make
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-staged-cross.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-staged-cross.patch
new file mode 100644
index 00000000000..7e4ea7a9f61
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-staged-cross.patch
@@ -0,0 +1,43 @@
+commit f2685df3b10e13f142736f28835e9064334bc143
+Author: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Wed Apr 5 22:31:37 2017 +0100
+
+ avoid $(CrossCompilerPrefix) for stage2 install
+
+ Suppose we are crossbuilding ghc (when ghc-stage2
+ is a normal compiler for $target):
+
+ For this case 'make install' should install unprefixed
+ stage2 'ghc' and not '$(CorssCompilePrefix)-ghc'.
+
+ That way cross-built ghc is installable and
+ usable on target as if it would be built natively
+ on a target.
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+diff --git a/mk/config.mk.in b/mk/config.mk.in
+index 4d5d82aa80..5e274bb71f 100644
+--- a/mk/config.mk.in
++++ b/mk/config.mk.in
+@@ -530,7 +530,7 @@ SUPPORTS_THIS_UNIT_ID = @SUPPORTS_THIS_UNIT_ID@
+ # needs to know which gcc you're using in order to perform its tests.
+
+ GccVersion = @GccVersion@
+-CrossCompilePrefix = @CrossCompilePrefix@
++
+ # TargetPlatformFull retains the string passed to configure so we have it in
+ # the necessary format to pass to libffi's configure.
+ TargetPlatformFull = @TargetPlatformFull@
+@@ -567,6 +567,11 @@ CrossCompiling = @CrossCompiling@
+ # See Note [Stage1Only vs stage=1]
+ Stage1Only = NO
+
++# Installed tools prefix:
++# we add prefix to crosscompiler GHC only (ghc-stage1),
++# not cross-built GHC (not ghc-stage2).
++CrossCompilePrefix = $(if $(filter YES,$(Stage1Only)),@CrossCompilePrefix@,)
++
+ # Install stage 2 by default, or stage 1 in the cross compiler
+ # case. Can be changed to 3
+ INSTALL_GHC_STAGE= $(if $(filter YES,$(Stage1Only)),1,2)
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-unphased-cross.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-unphased-cross.patch
new file mode 100644
index 00000000000..a5528956de1
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-unphased-cross.patch
@@ -0,0 +1,30 @@
+commit 6ff98b962db15d18eb1d082fe344cef692ecef8e
+Author: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Thu Apr 6 08:55:56 2017 +0100
+
+ config.mk.in: remove phase=0 hack for CrossCompilePrefix
+
+ $(CrossCompilePrefix) is used only in 'make install'
+ target filenames in $(DESTDIR). None of inplace (or boot)
+ files contain $(CrossCompilePrefix).
+
+ Thus we don't need to worry about phases.
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+diff --git a/mk/config.mk.in b/mk/config.mk.in
+index 4e61eea821..4d5d82aa80 100644
+--- a/mk/config.mk.in
++++ b/mk/config.mk.in
+@@ -530,11 +530,7 @@ SUPPORTS_THIS_UNIT_ID = @SUPPORTS_THIS_UNIT_ID@
+ # needs to know which gcc you're using in order to perform its tests.
+
+ GccVersion = @GccVersion@
+-ifeq "$(phase)" "0"
+-CrossCompilePrefix =
+-else
+ CrossCompilePrefix = @CrossCompilePrefix@
+-endif
+ # TargetPlatformFull retains the string passed to configure so we have it in
+ # the necessary format to pass to libffi's configure.
+ TargetPlatformFull = @TargetPlatformFull@
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-1.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-1.patch
new file mode 100644
index 00000000000..79751e1ecbd
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-1.patch
@@ -0,0 +1,124 @@
+commit a691f6a7a191a268380805481d8e63134764a4a1
+Author: Sergei Trofimovich <slyfox@inbox.ru>
+Date: Sat Apr 29 22:02:24 2017 +0100
+
+ add basic cross-compilation support (#87)
+
+ * fix include case: s/#include <Lmcons.h>/#include <lmcons.h>
+
+ Noticed when cross-compiling win32 on linux to i686-w64-mingw32-gcc.
+ i686-w64-mingw32 provides all headers in lowercase.
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+ * Pen.hsc: don't use c99-style comments in enum declarations
+
+ Ths change workarounds hsc2hs bug in cross-compile mode:
+ https://ghc.haskell.org/trac/ghc/ticket/13619
+
+ To reproduce the build failure it's enough to run
+ $ cabal configure --hsc2hs-options='--cross-safe --cross-compile'
+ $ cabal build --hsc2hs-options='--cross-safe --cross-compile'
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+ * SimpleMAPI.hsc: don't use #ifdef in enum declarations
+
+ This change workarounds hsc2hs bug in cross-compile mode:
+ https://ghc.haskell.org/trac/ghc/ticket/13620
+
+ To reproduce the build failure it's enough to run
+ $ cabal configure --hsc2hs-options='--cross-safe --cross-compile'
+ $ cabal build --hsc2hs-options='--cross-safe --cross-compile'
+
+ Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+
+diff --git a/Graphics/Win32/GDI/Pen.hsc b/Graphics/Win32/GDI/Pen.hsc
+index c880170..8d8df5d 100644
+--- a/Graphics/Win32/GDI/Pen.hsc
++++ b/Graphics/Win32/GDI/Pen.hsc
+@@ -56,7 +56,7 @@ foreign import WINDOWS_CCONV unsafe "windows.h DeleteObject"
+
+ type PenStyle = INT
+
+-#{enum PenStyle, // Pick one of these
++#{enum PenStyle,
+ , pS_SOLID = PS_SOLID // default
+ , pS_DASH = PS_DASH // -------
+ , pS_DOT = PS_DOT // .......
+@@ -69,14 +69,14 @@ type PenStyle = INT
+ , pS_STYLE_MASK = PS_STYLE_MASK // all the above
+ }
+
+-#{enum PenStyle , // "or" with one of these
++#{enum PenStyle,
+ , pS_ENDCAP_ROUND = PS_ENDCAP_ROUND // default
+ , pS_ENDCAP_SQUARE = PS_ENDCAP_SQUARE
+ , pS_ENDCAP_FLAT = PS_ENDCAP_FLAT
+ , pS_ENDCAP_MASK = PS_ENDCAP_MASK // all the above
+ }
+
+-#{enum PenStyle, // "or" with one of these
++#{enum PenStyle,
+ , pS_JOIN_ROUND = PS_JOIN_ROUND // default
+ , pS_JOIN_BEVEL = PS_JOIN_BEVEL
+ , pS_JOIN_MITER = PS_JOIN_MITER
+@@ -87,7 +87,7 @@ If PS_JOIN_MASK is not defined with your GNU Windows32 header files,
+ you'll have to define it.
+ -}
+
+-#{enum PenStyle, // "or" with one of these
++#{enum PenStyle,
+ , pS_COSMETIC = PS_COSMETIC // default
+ , pS_GEOMETRIC = PS_GEOMETRIC
+ , pS_TYPE_MASK = PS_TYPE_MASK // all the above
+diff --git a/System/Win32/Info/Computer.hsc b/System/Win32/Info/Computer.hsc
+index bb2eb72..65ae8dc 100644
+--- a/System/Win32/Info/Computer.hsc
++++ b/System/Win32/Info/Computer.hsc
+@@ -65,7 +65,7 @@ import System.Win32.Utils ( tryWithoutNull )
+ import System.Win32.Word ( DWORD, LPDWORD )
+
+ #include <windows.h>
+-#include <Lmcons.h>
++#include <lmcons.h>
+ #include "alignment.h"
+ ##include "windows_cconv.h"
+
+diff --git a/System/Win32/SimpleMAPI.hsc b/System/Win32/SimpleMAPI.hsc
+index 9727cfc..5ebf06b 100644
+--- a/System/Win32/SimpleMAPI.hsc
++++ b/System/Win32/SimpleMAPI.hsc
+@@ -53,12 +53,6 @@ type MapiFlag = ULONG
+ , mAPI_LOGON_UI = MAPI_LOGON_UI
+ , mAPI_NEW_SESSION = MAPI_NEW_SESSION
+ , mAPI_FORCE_DOWNLOAD = MAPI_FORCE_DOWNLOAD
+-#ifdef MAPI_LOGOFF_SHARED
+- , mAPI_LOGOFF_SHARED = MAPI_LOGOFF_SHARED
+-#endif
+-#ifdef MAPI_LOGOFF_UI
+- , mAPI_LOGOFF_UI = MAPI_LOGOFF_UI
+-#endif
+ , mAPI_DIALOG = MAPI_DIALOG
+ , mAPI_UNREAD_ONLY = MAPI_UNREAD_ONLY
+ , mAPI_LONG_MSGID = MAPI_LONG_MSGID
+@@ -74,6 +68,19 @@ type MapiFlag = ULONG
+ , mAPI_RECEIPT_REQUESTED = MAPI_RECEIPT_REQUESTED
+ , mAPI_SENT = MAPI_SENT
+ }
++-- Have to define enum values outside previous declaration due to
++-- hsc2hs bug in --cross-compile mode:
++-- https://ghc.haskell.org/trac/ghc/ticket/13620
++#ifdef MAPI_LOGOFF_SHARED
++#{enum MapiFlag,
++ , mAPI_LOGOFF_SHARED = MAPI_LOGOFF_SHARED
++}
++#endif
++#ifdef MAPI_LOGOFF_UI
++#{enum MapiFlag,
++ , mAPI_LOGOFF_UI = MAPI_LOGOFF_UI
++}
++#endif
+
+ mapiErrors :: [(ULONG,String)]
+ mapiErrors =
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-2-hack.patch b/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-2-hack.patch
new file mode 100644
index 00000000000..6fdcf2d1278
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc1-win32-cross-2-hack.patch
@@ -0,0 +1,144 @@
+hsc2hs can't detect values at compile-time if those are
+declared as pointers: https://github.com/haskell/win32/issues/88
+
+This patch is a huge hack: we encode absolute vaues from <windows.h>
+diff --git a/Graphics/Win32/GDI/Types.hsc b/Graphics/Win32/GDI/Types.hsc
+index c363530..8643cee 100644
+--- a/Graphics/Win32/GDI/Types.hsc
++++ b/Graphics/Win32/GDI/Types.hsc
+@@ -216,10 +216,10 @@ type HWND = HANDLE
+ type MbHWND = Maybe HWND
+
+ #{enum HWND, castUINTPtrToPtr
+- , hWND_BOTTOM = (UINT_PTR)HWND_BOTTOM
+- , hWND_NOTOPMOST = (UINT_PTR)HWND_NOTOPMOST
+- , hWND_TOP = (UINT_PTR)HWND_TOP
+- , hWND_TOPMOST = (UINT_PTR)HWND_TOPMOST
++ , hWND_BOTTOM = (UINT_PTR)(INT_PTR)(1)
++ , hWND_NOTOPMOST = (UINT_PTR)(INT_PTR)(-2)
++ , hWND_TOP = (UINT_PTR)(INT_PTR)(0)
++ , hWND_TOPMOST = (UINT_PTR)(INT_PTR)(-1)
+ }
+
+ type HMENU = HANDLE
+diff --git a/Graphics/Win32/Misc.hsc b/Graphics/Win32/Misc.hsc
+index 1248b5a..c791a20 100644
+--- a/Graphics/Win32/Misc.hsc
++++ b/Graphics/Win32/Misc.hsc
+@@ -67,23 +67,23 @@ foreign import WINDOWS_CCONV unsafe "windows.h LoadIconW"
+ c_LoadIcon :: HINSTANCE -> Icon -> IO HICON
+
+ #{enum Cursor, castUINTPtrToPtr
+- , iDC_ARROW = (UINT_PTR)IDC_ARROW
+- , iDC_IBEAM = (UINT_PTR)IDC_IBEAM
+- , iDC_WAIT = (UINT_PTR)IDC_WAIT
+- , iDC_CROSS = (UINT_PTR)IDC_CROSS
+- , iDC_UPARROW = (UINT_PTR)IDC_UPARROW
+- , iDC_SIZENWSE = (UINT_PTR)IDC_SIZENWSE
+- , iDC_SIZENESW = (UINT_PTR)IDC_SIZENESW
+- , iDC_SIZEWE = (UINT_PTR)IDC_SIZEWE
+- , iDC_SIZENS = (UINT_PTR)IDC_SIZENS
++ , iDC_ARROW = (UINT_PTR)(32512)
++ , iDC_IBEAM = (UINT_PTR)(32513)
++ , iDC_WAIT = (UINT_PTR)(32514)
++ , iDC_CROSS = (UINT_PTR)(32515)
++ , iDC_UPARROW = (UINT_PTR)(32516)
++ , iDC_SIZENWSE = (UINT_PTR)(32642)
++ , iDC_SIZENESW = (UINT_PTR)(32643)
++ , iDC_SIZEWE = (UINT_PTR)(32644)
++ , iDC_SIZENS = (UINT_PTR)(32645)
+ }
+
+ #{enum Icon, castUINTPtrToPtr
+- , iDI_APPLICATION = (UINT_PTR)IDI_APPLICATION
+- , iDI_HAND = (UINT_PTR)IDI_HAND
+- , iDI_QUESTION = (UINT_PTR)IDI_QUESTION
+- , iDI_EXCLAMATION = (UINT_PTR)IDI_EXCLAMATION
+- , iDI_ASTERISK = (UINT_PTR)IDI_ASTERISK
++ , iDI_APPLICATION = (UINT_PTR)(32512)
++ , iDI_HAND = (UINT_PTR)(32513)
++ , iDI_QUESTION = (UINT_PTR)(32514)
++ , iDI_EXCLAMATION = (UINT_PTR)(32515)
++ , iDI_ASTERISK = (UINT_PTR)(32516)
+ }
+
+ ----------------------------------------------------------------
+diff --git a/Graphics/Win32/Resource.hsc b/Graphics/Win32/Resource.hsc
+index e8ad565..ca58fa2 100644
+--- a/Graphics/Win32/Resource.hsc
++++ b/Graphics/Win32/Resource.hsc
+@@ -61,23 +61,23 @@ foreign import WINDOWS_CCONV unsafe "windows.h EndUpdateResourceW"
+ type ResourceType = LPCTSTR
+
+ #{enum ResourceType, castUINTPtrToPtr
+- , rT_ACCELERATOR = (UINT_PTR)RT_ACCELERATOR // Accelerator table
+- , rT_ANICURSOR = (UINT_PTR)RT_ANICURSOR // Animated cursor
+- , rT_ANIICON = (UINT_PTR)RT_ANIICON // Animated icon
+- , rT_BITMAP = (UINT_PTR)RT_BITMAP // Bitmap resource
+- , rT_CURSOR = (UINT_PTR)RT_CURSOR // Hardware-dependent cursor resource
+- , rT_DIALOG = (UINT_PTR)RT_DIALOG // Dialog box
+- , rT_FONT = (UINT_PTR)RT_FONT // Font resource
+- , rT_FONTDIR = (UINT_PTR)RT_FONTDIR // Font directory resource
+- , rT_GROUP_CURSOR = (UINT_PTR)RT_GROUP_CURSOR // Hardware-independent cursor resource
+- , rT_GROUP_ICON = (UINT_PTR)RT_GROUP_ICON // Hardware-independent icon resource
+- , rT_HTML = (UINT_PTR)RT_HTML // HTML document
+- , rT_ICON = (UINT_PTR)RT_ICON // Hardware-dependent icon resource
+- , rT_MENU = (UINT_PTR)RT_MENU // Menu resource
+- , rT_MESSAGETABLE = (UINT_PTR)RT_MESSAGETABLE // Message-table entry
+- , rT_RCDATA = (UINT_PTR)RT_RCDATA // Application-defined resource (raw data)
+- , rT_STRING = (UINT_PTR)RT_STRING // String-table entry
+- , rT_VERSION = (UINT_PTR)RT_VERSION // Version resource
++ , rT_ACCELERATOR = (UINT_PTR)(9)
++ , rT_ANICURSOR = (UINT_PTR)(21)
++ , rT_ANIICON = (UINT_PTR)(22)
++ , rT_BITMAP = (UINT_PTR)(2)
++ , rT_CURSOR = (UINT_PTR)(1)
++ , rT_DIALOG = (UINT_PTR)(5)
++ , rT_FONT = (UINT_PTR)(8)
++ , rT_FONTDIR = (UINT_PTR)(7)
++ , rT_GROUP_CURSOR = (UINT_PTR)(1 + DIFFERENCE)
++ , rT_GROUP_ICON = (UINT_PTR)(3 + DIFFERENCE)
++ , rT_HTML = (UINT_PTR)(23)
++ , rT_ICON = (UINT_PTR)(3)
++ , rT_MENU = (UINT_PTR)(4)
++ , rT_MESSAGETABLE = (UINT_PTR)(11)
++ , rT_RCDATA = (UINT_PTR)(10)
++ , rT_STRING = (UINT_PTR)(6)
++ , rT_VERSION = (UINT_PTR)(16)
+ }
+
+ findResource :: HMODULE -> String -> ResourceType -> IO HRSRC
+diff --git a/Graphics/Win32/Window/PostMessage.hsc b/Graphics/Win32/Window/PostMessage.hsc
+index 7f4c9f0..609f3f6 100644
+--- a/Graphics/Win32/Window/PostMessage.hsc
++++ b/Graphics/Win32/Window/PostMessage.hsc
+@@ -41,7 +41,7 @@ foreign import WINDOWS_CCONV "windows.h PostThreadMessageW"
+ c_PostThreadMessage :: DWORD -> WindowMessage -> WPARAM -> LPARAM -> IO BOOL
+
+ #{enum HWND, castUINTPtrToPtr
+- , hWND_BROADCAST = (UINT_PTR)HWND_BROADCAST
++ , hWND_BROADCAST = (UINT_PTR)(0xffff)
+ }
+
+ foreign import WINDOWS_CCONV "windows.h InSendMessage"
+diff --git a/System/Win32/Registry.hsc b/System/Win32/Registry.hsc
+index afbb011..c7edfc1 100644
+--- a/System/Win32/Registry.hsc
++++ b/System/Win32/Registry.hsc
+@@ -80,11 +80,11 @@ import System.Win32.Types (castUINTPtrToPtr, failUnlessSuccessOr, maybePtr)
+ #include <windows.h>
+
+ #{enum HKEY, (unsafePerformIO . newForeignHANDLE . castUINTPtrToPtr)
+- , hKEY_CLASSES_ROOT = (UINT_PTR)HKEY_CLASSES_ROOT
+- , hKEY_CURRENT_CONFIG = (UINT_PTR)HKEY_CURRENT_CONFIG
+- , hKEY_CURRENT_USER = (UINT_PTR)HKEY_CURRENT_USER
+- , hKEY_LOCAL_MACHINE = (UINT_PTR)HKEY_LOCAL_MACHINE
+- , hKEY_USERS = (UINT_PTR)HKEY_USERS
++ , hKEY_CLASSES_ROOT = (UINT_PTR)(0x80000000)
++ , hKEY_CURRENT_CONFIG = (UINT_PTR)(0x80000005)
++ , hKEY_CURRENT_USER = (UINT_PTR)(0x80000001)
++ , hKEY_LOCAL_MACHINE = (UINT_PTR)(0x80000002)
++ , hKEY_USERS = (UINT_PTR)(0x80000003)
+ }
+ -- , PKEYERFORMANCE_DATA NT only
+ -- , HKEY_DYN_DATA 95/98 only
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc2-O2-unreg.patch b/dev-lang/ghc/files/ghc-8.2.1_rc2-O2-unreg.patch
new file mode 100644
index 00000000000..00f9ca4fdff
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc2-O2-unreg.patch
@@ -0,0 +1,35 @@
+ghc -O2 generates too large C files for unregisterised compiler.
+On ia64 it causes DynFlags to compile for 60 minutes (then assembler
+crashes).
+
+To decrease C code inflation we don't use -O2 in UNREG mode.
+diff --git a/mk/config.mk.in b/mk/config.mk.in
+index 4e61eea..15a56e9 100644
+--- a/mk/config.mk.in
++++ b/mk/config.mk.in
+@@ -72,11 +72,2 @@ GhcStage3HcOpts=-O2
+
+-# Disable -O2 optimization. Otherwise amount of generated C code
+-# makes things very slow to compile (~5 minutes on core-i7 for 'compiler/hsSyn/HsExpr.hs')
+-# and sometimes not compile at all (powerpc64 overflows something
+-# on 'compiler/hsSyn/HsExpr.hs').
+-ifeq "$(GhcUnregisterised)" "YES"
+-GhcStage1HcOpts=
+-GhcStage2HcOpts=
+-GhcStage3HcOpts=
+-endif
+
+@@ -904 +895,13 @@ CURSES_INCLUDE_DIRS = @CURSES_INCLUDE_DIRS@
+ CURSES_LIB_DIRS = @CURSES_LIB_DIRS@
++
++# Disable -O2 optimization. Otherwise amount of generated C code
++# makes things very slow to compile (~5 minutes on core-i7 for 'compiler/hsSyn/HsExpr.hs')
++# and sometimes not compile at all (powerpc64 overflows something
++# on 'compiler/hsSyn/HsExpr.hs').
++ifeq "$(GhcUnregisterised)" "YES"
++GhcStage1HcOpts=
++GhcStage2HcOpts=
++GhcStage3HcOpts=
++
++GhcLibHcOpts=
++endif
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc3-any-vendor.patch b/dev-lang/ghc/files/ghc-8.2.1_rc3-any-vendor.patch
new file mode 100644
index 00000000000..b55e37a8bf9
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc3-any-vendor.patch
@@ -0,0 +1,44 @@
+From c2303dff95aa174021a1950656fdf9a1cf983959 Mon Sep 17 00:00:00 2001
+From: Sergei Trofimovich <slyfox@gentoo.org>
+Date: Sat, 8 Jul 2017 09:47:12 +0100
+Subject: [PATCH] aclocal.m4: allow arbitrary <vendor> string in toolchain
+ triplets
+
+Canonical triplets have a form of
+ <arch>-<vendor>-<os>[-<abi>]
+
+Checking for vendor is almost never correct as it's an
+arbitrary string.
+
+It's useful to have multiple "vendors" to denote
+otherwise the same (WRT <arch>, <os>, <abi>) target:
+ --target=x86_64-pc-linux-gnu
+ --target=x86_64-unknown-linux-gnu
+ --target=x86_64-ghc80-linux-gnu
+ --target=x86_64-ghchead-linux-gnu
+
+Do not fail unknown vendors. Only emit a warning.
+Ideally configure checks should never use "vendor".
+
+Signed-off-by: Sergei Trofimovich <slyfox@gentoo.org>
+---
+ aclocal.m4 | 3 +--
+ 1 file changed, 1 insertion(+), 2 deletions(-)
+
+diff --git a/aclocal.m4 b/aclocal.m4
+index 001f813dfc..1d9c09b0cd 100644
+--- a/aclocal.m4
++++ b/aclocal.m4
+@@ -230,8 +230,7 @@ AC_DEFUN([FPTOOLS_SET_HASKELL_PLATFORM_VARS],
+ dec|none|unknown|hp|apple|next|sun|sgi|ibm|montavista|portbld)
+ ;;
+ *)
+- echo "Unknown vendor [$]1"
+- exit 1
++ AC_MSG_WARN([Unknown vendor [$]1])
+ ;;
+ esac
+ }
+--
+2.13.3
+
diff --git a/dev-lang/ghc/files/ghc-8.2.1_rc3-stginit-data.patch b/dev-lang/ghc/files/ghc-8.2.1_rc3-stginit-data.patch
new file mode 100644
index 00000000000..81e751d778c
--- /dev/null
+++ b/dev-lang/ghc/files/ghc-8.2.1_rc3-stginit-data.patch
@@ -0,0 +1,27 @@
+Fix label type for __stginit_* labels: those are .data labels, not .text
+
+Noticed when was building --enable-unregisterised build for x86_64:
+
+/tmp/ghc22931_0/ghc_3.hc:5:9: error:
+ error: '__stginit_ghczmprim_GHCziTypes' redeclared as different kind of symbol
+ StgWord __stginit_ghczmprim_GHCziTypes[]__attribute__((aligned(8)))= {
+ ^~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+ |
+5 | StgWord __stginit_ghczmprim_GHCziTypes[]__attribute__((aligned(8)))= {
+ | ^
+
+In file included from /tmp/ghc22931_0/ghc_3.hc:3:0: error:
+
+/tmp/ghc22931_0/ghc_3.hc:4:5: error:
+ note: previous declaration of '__stginit_ghczmprim_GHCziTypes' was here
+ EF_(__stginit_ghczmprim_GHCziTypes);
+ ^
+diff --git a/compiler/cmm/CLabel.hs b/compiler/cmm/CLabel.hs
+index 77a889a..05d71ab 100644
+--- a/compiler/cmm/CLabel.hs
++++ b/compiler/cmm/CLabel.hs
+@@ -956,3 +956,3 @@ labelType (CaseLabel _ CaseReturnInfo) = DataLabel
+ labelType (CaseLabel _ _) = CodeLabel
+-labelType (PlainModuleInitLabel _) = CodeLabel
++labelType (PlainModuleInitLabel _) = DataLabel
+ labelType (SRTLabel _) = DataLabel