[commit: ghc] wip/ttg5-data-2017-11-15: Reduce compile time memory usage by splitting HsInstances (75a4a5d)

git at git.haskell.org git at git.haskell.org
Wed Nov 15 20:58:36 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/ttg5-data-2017-11-15
Link       : http://ghc.haskell.org/trac/ghc/changeset/75a4a5d4b373a512fbebf8bc79f1d2da1ac394b7/ghc

>---------------------------------------------------------------

commit 75a4a5d4b373a512fbebf8bc79f1d2da1ac394b7
Author: Alan Zimmerman <alan.zimm at gmail.com>
Date:   Wed Nov 15 20:49:54 2017 +0200

    Reduce compile time memory usage by splitting HsInstances
    
    On my machine, compiling with GHC 8.2.1, Compililing HsInstances.hs takes around
    3.2G (via top, rss)
    
    compiling using the generated ghc-stage1 uses 5.9G


>---------------------------------------------------------------

75a4a5d4b373a512fbebf8bc79f1d2da1ac394b7
 compiler/hsSyn/HsExpr.hs-boot       |  8 --------
 compiler/hsSyn/HsInstances.hs       | 18 +++++++++---------
 compiler/hsSyn/HsInstances.hs-boot  | 20 ++++++++++++++++++++
 compiler/hsSyn/HsInstances2.hs      | 11 +++++------
 compiler/hsSyn/HsInstances2.hs-boot | 31 +++++++++++++++++++++++++++++++
 compiler/hsSyn/HsPat.hs-boot        |  1 -
 compiler/hsSyn/HsSyn.hs             |  1 -
 7 files changed, 65 insertions(+), 25 deletions(-)

diff --git a/compiler/hsSyn/HsExpr.hs-boot b/compiler/hsSyn/HsExpr.hs-boot
index 03a18a3..b149151 100644
--- a/compiler/hsSyn/HsExpr.hs-boot
+++ b/compiler/hsSyn/HsExpr.hs-boot
@@ -14,7 +14,6 @@ import Outputable ( SDoc, Outputable )
 import {-# SOURCE #-} HsPat  ( LPat )
 import BasicTypes ( SpliceExplicitFlag(..))
 import HsExtension ( OutputableBndrId, SourceTextX, GhcPass )
-import Data.Data hiding ( Fixity )
 
 type role HsExpr nominal
 type role HsCmd nominal
@@ -29,13 +28,6 @@ data MatchGroup (a :: *) (body :: *)
 data GRHSs (a :: *) (body :: *)
 data SyntaxExpr (i :: *)
 
--- instance (DataIdLR p p) => Data (HsSplice p)
--- instance (DataIdLR p p) => Data (HsExpr p)
--- instance (DataIdLR p p) => Data (HsCmd p)
--- instance (Data body,DataIdLR p p) => Data (MatchGroup p body)
--- instance (Data body,DataIdLR p p) => Data (GRHSs p body)
--- instance (DataIdLR p p) => Data (SyntaxExpr p)
-
 instance (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
        => Outputable (HsExpr (GhcPass p))
 instance (SourceTextX (GhcPass p), OutputableBndrId (GhcPass p))
diff --git a/compiler/hsSyn/HsInstances.hs b/compiler/hsSyn/HsInstances.hs
index fc871f1..169199e 100644
--- a/compiler/hsSyn/HsInstances.hs
+++ b/compiler/hsSyn/HsInstances.hs
@@ -4,7 +4,7 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
-{-# GHC_OPTIONS -fno-warn-orphans #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
 module HsInstances where
 
 -- This module defines the Data instances for the hsSyn AST.
@@ -14,16 +14,16 @@ module HsInstances where
 
 -- UndecidableInstances ?
 
-import GhcPrelude
+import {-# SOURCE #-} HsInstances2 ()
 import Data.Data hiding ( Fixity )
 
 import HsExtension
 import HsBinds
 import HsDecls
-import HsExpr
-import HsLit
+-- import HsExpr
+-- import HsLit
 import HsTypes
-import HsPat
+-- import HsPat
 
 -- Data derivations from HsBinds ---------------------------------------
 
@@ -55,8 +55,9 @@ deriving instance (DataIdLR p p) => Data (HsDerivingClause p)
 deriving instance (DataIdLR p p) => Data (ConDecl p)
 deriving instance DataIdLR p p   => Data (TyFamInstDecl p)
 deriving instance DataIdLR p p   => Data (DataFamInstDecl p)
+deriving instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p)   (HsDataDefn p))
+deriving instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p)   (LHsType p))
 deriving instance (DataIdLR p p) => Data (FamEqn p (LHsQTyVars p) (LHsType p))
-deriving instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p) (HsDataDefn p))
 deriving instance (DataIdLR p p) => Data (ClsInstDecl p)
 deriving instance (DataIdLR p p) => Data (InstDecl p)
 deriving instance (DataIdLR p p) => Data (DerivDecl p)
@@ -70,10 +71,9 @@ deriving instance (DataId p)     => Data (WarnDecls p)
 deriving instance (DataId p)     => Data (WarnDecl p)
 deriving instance (DataIdLR p p) => Data (AnnDecl p)
 deriving instance (DataId p)     => Data (RoleAnnotDecl p)
-deriving instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p) (LHsType p))
 
 -- Data derivations from HsExpr ----------------------------------------
-
+{-
 deriving instance (DataIdLR p p) => Data (SyntaxExpr p)
 deriving instance (DataIdLR p p) => Data (HsExpr p)
 deriving instance (DataIdLR p p) => Data (HsTupArg p)
@@ -128,5 +128,5 @@ deriving instance DataId p               => Data (AmbiguousFieldOcc p)
 deriving instance (DataIdLR p p) => Data (Pat p)
 deriving instance (DataIdLR p p) => Data (HsRecFields p (LPat p))
 deriving instance (DataIdLR p p) => Data (HsRecFields p (LHsExpr p))
-
+-}
 -- ---------------------------------------------------------------------
diff --git a/compiler/hsSyn/HsInstances.hs-boot b/compiler/hsSyn/HsInstances.hs-boot
new file mode 100644
index 0000000..3dda7e8
--- /dev/null
+++ b/compiler/hsSyn/HsInstances.hs-boot
@@ -0,0 +1,20 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+module HsInstances where
+
+import Data.Data hiding ( Fixity )
+import HsExtension ( DataIdLR )
+import HsBinds
+import HsDecls
+import HsTypes
+
+instance (DataIdLR p p) => Data (VectDecl p)
+instance (DataIdLR pL pR) => Data (HsLocalBindsLR pL pR)
+instance (DataIdLR p p) => Data (HsDecl p)
+instance (DataIdLR p p) => Data (HsGroup p)
+instance (DataIdLR pL pL) => Data (NHsValBindsLR pL)
+instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p)   (HsDataDefn p))
+instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p)   (LHsType p))
diff --git a/compiler/hsSyn/HsInstances2.hs b/compiler/hsSyn/HsInstances2.hs
index 1e5ee72..2250387 100644
--- a/compiler/hsSyn/HsInstances2.hs
+++ b/compiler/hsSyn/HsInstances2.hs
@@ -4,8 +4,8 @@
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE FlexibleInstances #-}
 {-# LANGUAGE UndecidableInstances #-}
-{-# GHC_OPTIONS -fno-warn-orphans #-}
-module HsInstances where
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+module HsInstances2 where
 
 -- This module defines the Data instances for the hsSyn AST.
 
@@ -14,12 +14,11 @@ module HsInstances where
 
 -- UndecidableInstances ?
 
-import GhcPrelude
 import Data.Data hiding ( Fixity )
 
-import {-#
+import {-# SOURCE #-} HsInstances ()
 import HsExtension
-import HsBinds
+-- import HsBinds
 import HsDecls
 import HsExpr
 import HsLit
@@ -72,7 +71,7 @@ deriving instance (DataId p)     => Data (WarnDecl p)
 deriving instance (DataIdLR p p) => Data (AnnDecl p)
 deriving instance (DataId p)     => Data (RoleAnnotDecl p)
 deriving instance (DataIdLR p p) => Data (FamEqn p (HsTyPats p) (LHsType p))
-
+-}
 -- Data derivations from HsExpr ----------------------------------------
 
 deriving instance (DataIdLR p p) => Data (SyntaxExpr p)
diff --git a/compiler/hsSyn/HsInstances2.hs-boot b/compiler/hsSyn/HsInstances2.hs-boot
new file mode 100644
index 0000000..16ac7ee
--- /dev/null
+++ b/compiler/hsSyn/HsInstances2.hs-boot
@@ -0,0 +1,31 @@
+{-# LANGUAGE TypeFamilies #-}
+{-# LANGUAGE FlexibleContexts #-}
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE UndecidableInstances #-}
+{-# OPTIONS_GHC -fno-warn-orphans #-}
+module HsInstances2 where
+
+
+import Data.Data hiding ( Fixity )
+import HsExtension ( DataIdLR )
+import HsDecls
+import HsExpr
+import HsTypes
+import HsPat
+
+instance (DataIdLR p p) => Data (HsExpr p)
+instance (DataIdLR p p) => Data (HsTyVarBndr p)
+instance (DataIdLR p p) => Data (HsType p)
+instance (DataIdLR p p)         => Data (LHsQTyVars p)
+instance (DataIdLR p p) => Data (HsImplicitBndrs p (LHsType p))
+instance (DataIdLR p p) => Data (HsImplicitBndrs p (FamEqn p (HsTyPats p) (HsDataDefn p)))
+instance (DataIdLR p p) => Data (HsImplicitBndrs p (FamEqn p (HsTyPats p) (LHsType p)))
+instance (DataIdLR p p) => Data (HsWildCardBndrs p (LHsSigType p))
+instance (DataIdLR p p) => Data (ConDeclField p)
+
+instance (DataIdLR p p) => Data (HsSplice p)
+instance (DataIdLR p p) => Data (MatchGroup p (LHsExpr p))
+
+instance (DataIdLR p p) => Data (Pat p)
+
+instance (DataIdLR p p) => Data (GRHSs      p (LHsExpr p))
diff --git a/compiler/hsSyn/HsPat.hs-boot b/compiler/hsSyn/HsPat.hs-boot
index dfd5359..203209d 100644
--- a/compiler/hsSyn/HsPat.hs-boot
+++ b/compiler/hsSyn/HsPat.hs-boot
@@ -9,7 +9,6 @@
 module HsPat where
 import SrcLoc( Located )
 
-import Data.Data hiding (Fixity)
 import Outputable
 import HsExtension      ( SourceTextX, OutputableBndrId, GhcPass )
 
diff --git a/compiler/hsSyn/HsSyn.hs b/compiler/hsSyn/HsSyn.hs
index 83147b6..54ba278 100644
--- a/compiler/hsSyn/HsSyn.hs
+++ b/compiler/hsSyn/HsSyn.hs
@@ -32,7 +32,6 @@ module HsSyn (
         Fixity,
 
         HsModule(..),
-        HsInstances
 ) where
 
 -- friends:



More information about the ghc-commits mailing list