[commit: ghc] wip/ttg5-data-2017-11-17: Add dummy types to force GHC make to build boot files (315be16)
git at git.haskell.org
git at git.haskell.org
Sat Nov 18 09:36:12 UTC 2017
Repository : ssh://git@git.haskell.org/ghc
On branch : wip/ttg5-data-2017-11-17
Link : http://ghc.haskell.org/trac/ghc/changeset/315be165b54dda7aed8d4044780ef29539071a18/ghc
>---------------------------------------------------------------
commit 315be165b54dda7aed8d4044780ef29539071a18
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date: Sat Nov 18 11:10:53 2017 +0200
Add dummy types to force GHC make to build boot files
>---------------------------------------------------------------
315be165b54dda7aed8d4044780ef29539071a18
compiler/hsSyn/HsInstances.hs | 5 ++++-
compiler/hsSyn/HsInstances.hs-boot | 2 ++
compiler/hsSyn/HsInstances2.hs | 5 ++++-
compiler/hsSyn/HsInstances2.hs-boot | 2 ++
4 files changed, 12 insertions(+), 2 deletions(-)
diff --git a/compiler/hsSyn/HsInstances.hs b/compiler/hsSyn/HsInstances.hs
index a674212..6b39c9a 100644
--- a/compiler/hsSyn/HsInstances.hs
+++ b/compiler/hsSyn/HsInstances.hs
@@ -14,13 +14,16 @@ module HsInstances where
-- UndecidableInstances ?
-import {-# SOURCE #-} HsInstances2 ()
+import {-# SOURCE #-} HsInstances2 ( DummyHsInstances2 )
import Data.Data hiding ( Fixity )
import HsExtension
import HsBinds
import HsDecls
+data DummyHsInstancesSeq
+data DummyHsInstances p = DI (DummyHsInstances2 p)
+
-- Data derivations from HsBinds ---------------------------------------
deriving instance (DataIdLR pL pR) => Data (HsLocalBindsLR pL pR)
diff --git a/compiler/hsSyn/HsInstances.hs-boot b/compiler/hsSyn/HsInstances.hs-boot
index a942e86..f17d934 100644
--- a/compiler/hsSyn/HsInstances.hs-boot
+++ b/compiler/hsSyn/HsInstances.hs-boot
@@ -10,6 +10,8 @@ import HsExtension ( DataIdLR )
import HsBinds
import HsDecls
+data DummyHsInstances (i :: *)
+
instance (DataIdLR p p) => Data (VectDecl p)
instance (DataIdLR pL pR) => Data (HsLocalBindsLR pL pR)
instance (DataIdLR p p) => Data (HsDecl p)
diff --git a/compiler/hsSyn/HsInstances2.hs b/compiler/hsSyn/HsInstances2.hs
index b0502c8..92d2f31 100644
--- a/compiler/hsSyn/HsInstances2.hs
+++ b/compiler/hsSyn/HsInstances2.hs
@@ -16,13 +16,16 @@ module HsInstances2 where
import Data.Data hiding ( Fixity )
-import {-# SOURCE #-} HsInstances ()
+import {-# SOURCE #-} HsInstances ( DummyHsInstances )
import HsExtension
import HsExpr
import HsLit
import HsTypes
import HsPat
+data DummyHsInstances2 p = DI2 (DummyHsInstances p)
+
+
-- Data derivations from HsBinds ---------------------------------------
{-
deriving instance (DataIdLR pL pR) => Data (HsLocalBindsLR pL pR)
diff --git a/compiler/hsSyn/HsInstances2.hs-boot b/compiler/hsSyn/HsInstances2.hs-boot
index 33c7356..f9de5b7 100644
--- a/compiler/hsSyn/HsInstances2.hs-boot
+++ b/compiler/hsSyn/HsInstances2.hs-boot
@@ -12,6 +12,8 @@ import HsExpr
import HsTypes
import HsPat
+data DummyHsInstances2 (i :: *)
+
instance (DataIdLR p p) => Data (HsExpr p)
instance (DataIdLR p p) => Data (HsTyVarBndr p)
instance (DataIdLR p p) => Data (HsType p)
More information about the ghc-commits
mailing list