[commit: ghc] master: Make template-haskell build with GHC 7.6, fixes bootstrap build. (ef7ed16)
git at git.haskell.org
git at git.haskell.org
Tue May 12 04:34:49 UTC 2015
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/ef7ed16c8a34e5ab26a23264f02aa6391c338884/ghc
>---------------------------------------------------------------
commit ef7ed16c8a34e5ab26a23264f02aa6391c338884
Author: Edward Z. Yang <ezyang at cs.stanford.edu>
Date: Mon May 11 15:48:35 2015 -0700
Make template-haskell build with GHC 7.6, fixes bootstrap build.
Signed-off-by: Edward Z. Yang <ezyang at cs.stanford.edu>
Test Plan: validate on 7.6
Reviewers: austin, goldfire
Subscribers: bgamari, thomie
Differential Revision: https://phabricator.haskell.org/D885
>---------------------------------------------------------------
ef7ed16c8a34e5ab26a23264f02aa6391c338884
libraries/template-haskell/Language/Haskell/TH/Syntax.hs | 11 ++++++++++-
libraries/template-haskell/template-haskell.cabal | 3 +--
mk/warnings.mk | 4 ----
3 files changed, 11 insertions(+), 7 deletions(-)
diff --git a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
index 8879c62..a6f970d 100644
--- a/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
+++ b/libraries/template-haskell/Language/Haskell/TH/Syntax.hs
@@ -1,5 +1,12 @@
{-# LANGUAGE CPP, DeriveDataTypeable, PolymorphicComponents,
- RoleAnnotations, DeriveGeneric, FlexibleInstances #-}
+ DeriveGeneric, FlexibleInstances #-}
+
+#if __GLASGOW_HASKELL__ >= 707
+{-# LANGUAGE RoleAnnotations #-}
+{-# OPTIONS_GHC -fno-warn-inline-rule-shadowing #-}
+#else
+{-# OPTIONS_GHC -w #-} -- -fno-warn-inline-rule-shadowing doesn't exist
+#endif
#if MIN_VERSION_base(4,8,0)
#define HAS_NATURAL
@@ -170,7 +177,9 @@ instance Applicative Q where
--
-----------------------------------------------------
+#if __GLASGOW_HASKELL__ >= 707
type role TExp nominal -- See Note [Role of TExp]
+#endif
newtype TExp a = TExp { unType :: Exp }
unTypeQ :: Q (TExp a) -> Q Exp
diff --git a/libraries/template-haskell/template-haskell.cabal b/libraries/template-haskell/template-haskell.cabal
index bd277d1..de71132 100644
--- a/libraries/template-haskell/template-haskell.cabal
+++ b/libraries/template-haskell/template-haskell.cabal
@@ -31,7 +31,6 @@ Library
MagicHash
PolymorphicComponents
RankNTypes
- RoleAnnotations
ScopedTypeVariables
TemplateHaskell
UnboxedTuples
@@ -48,7 +47,7 @@ Library
Language.Haskell.TH.Lib.Map
build-depends:
- base >= 4.7 && < 4.9,
+ base >= 4.6 && < 4.9,
pretty == 1.1.*
-- We need to set the package key to template-haskell (without a
diff --git a/mk/warnings.mk b/mk/warnings.mk
index 5c41d5f..22acf9a 100644
--- a/mk/warnings.mk
+++ b/mk/warnings.mk
@@ -101,10 +101,6 @@ libraries/base_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe
libraries/ghc-prim_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe
libraries/Win32_dist-install_EXTRA_HC_OPTS += -fno-warn-trustworthy-safe
-# Temporarely disable inline rule shadowing warning
-libraries/template-haskell_dist-boot_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing
-libraries/template-haskell_dist-install_EXTRA_HC_OPTS += -fno-warn-inline-rule-shadowing
-
# We need -fno-warn-deprecated-flags to avoid failure with -Werror
GhcLibExtraHcOpts += -fno-warn-deprecated-flags
GhcBootLibExtraHcOpts += -fno-warn-deprecated-flags
More information about the ghc-commits
mailing list