[Git][ghc/ghc][wip/T18645] Hackily decouple the parser from the desugarer

Sebastian Graf gitlab at gitlab.haskell.org
Thu Sep 10 14:04:59 UTC 2020



Sebastian Graf pushed to branch wip/T18645 at Glasgow Haskell Compiler / GHC


Commits:
9280042c by Sebastian Graf at 2020-09-10T16:04:51+02:00
Hackily decouple the parser from the desugarer

In a hopefully temporary hack, I re-used the idea from !1957 of using a
nullary type family to break the dependency from GHC.Driver.Hooks on the
definition of DsM ("Abstract Data").
This in turn broke the last dependency from the parser to the desugarer.
More details in `Note [The Decoupling Abstract Data Hack]`.

In the future, we hope to undo this hack again in favour of breaking the
dependency from the parser to DynFlags altogether.

- - - - -


2 changed files:

- compiler/GHC/Driver/Hooks.hs
- compiler/GHC/HsToCore/Types.hs


Changes:

=====================================
compiler/GHC/Driver/Hooks.hs
=====================================
@@ -3,7 +3,7 @@
 -- NB: this module is SOURCE-imported by DynFlags, and should primarily
 --     refer to *types*, rather than *code*
 
-{-# LANGUAGE CPP, RankNTypes #-}
+{-# LANGUAGE CPP, RankNTypes, TypeFamilies #-}
 
 module GHC.Driver.Hooks
    ( Hooks
@@ -11,6 +11,7 @@ module GHC.Driver.Hooks
    , lookupHook
    , getHooked
      -- the hooks:
+   , DsForeignsHook
    , dsForeignsHook
    , tcForeignImportsHook
    , tcForeignExportsHook
@@ -36,9 +37,7 @@ import GHC.Driver.Types
 import GHC.Hs.Decls
 import GHC.Hs.Binds
 import GHC.Hs.Expr
-import GHC.Data.OrdList
 import GHC.Tc.Types
-import GHC.HsToCore.Types
 import GHC.Data.Bag
 import GHC.Types.Name.Reader
 import GHC.Types.Name
@@ -59,6 +58,7 @@ import GHC.Hs.Extension
 import GHC.StgToCmm.Types (ModuleLFInfos)
 
 import Data.Maybe
+import qualified Data.Kind
 
 {-
 ************************************************************************
@@ -90,9 +90,32 @@ emptyHooks = Hooks
   , cmmToRawCmmHook        = Nothing
   }
 
+{- Note [The Decoupling Abstract Data Hack]
+~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
+The "Abstract Data" idea is due to Richard Eisenberg in
+https://gitlab.haskell.org/ghc/ghc/-/merge_requests/1957, where the pattern is
+described in more detail.
+
+Here we use it as a temporary measure to break the dependency from the Parser on
+the Desugarer until the parser is free of DynFlags. We introduced a nullary type
+family @DsForeignsook@, whose single definition is in GHC.HsToCore.Types, where
+we instantiate it to
+
+   [LForeignDecl GhcTc] -> DsM (ForeignStubs, OrdList (Id, CoreExpr))
+
+In doing so, the Hooks module (which is an hs-boot dependency of DynFlags) can
+be decoupled from its use of the DsM definition in GHC.HsToCore.Types. Since
+both DsM and the definition of @ForeignsHook@ live in the same module, there is
+virtually no difference for plugin authors that want to write a foreign hook.
+-}
+
+-- See Note [The Decoupling Abstract Data Hack]
+type family DsForeignsHook :: Data.Kind.Type
+
 data Hooks = Hooks
-  { dsForeignsHook         :: Maybe ([LForeignDecl GhcTc]
-                           -> DsM (ForeignStubs, OrdList (Id, CoreExpr)))
+  { dsForeignsHook         :: Maybe DsForeignsHook
+  -- ^ Actual type:
+  -- @Maybe ([LForeignDecl GhcTc] -> DsM (ForeignStubs, OrdList (Id, CoreExpr)))@
   , tcForeignImportsHook   :: Maybe ([LForeignDecl GhcRn]
                           -> TcM ([Id], [LForeignDecl GhcTc], Bag GlobalRdrElt))
   , tcForeignExportsHook   :: Maybe ([LForeignDecl GhcRn]


=====================================
compiler/GHC/HsToCore/Types.hs
=====================================
@@ -1,3 +1,5 @@
+{-# LANGUAGE TypeFamilies, UndecidableInstances #-}
+
 -- | Various types used during desugaring.
 module GHC.HsToCore.Types (
         DsM, DsLclEnv(..), DsGblEnv(..),
@@ -10,13 +12,17 @@ import GHC.Types.CostCentre.State
 import GHC.Types.Name.Env
 import GHC.Types.SrcLoc
 import GHC.Types.Var
-import GHC.Hs (HsExpr, GhcTc)
+import GHC.Hs (LForeignDecl, HsExpr, GhcTc)
 import GHC.Tc.Types (TcRnIf, IfGblEnv, IfLclEnv, CompleteMatches)
 import {-# SOURCE #-} GHC.HsToCore.PmCheck.Types (Nablas)
+import GHC.Core (CoreExpr)
 import GHC.Core.FamInstEnv
 import GHC.Utils.Error
 import GHC.Utils.Outputable as Outputable
 import GHC.Unit.Module
+import GHC.Driver.Hooks (DsForeignsHook)
+import GHC.Data.OrdList (OrdList)
+import GHC.Driver.Types (ForeignStubs)
 
 {-
 ************************************************************************
@@ -75,3 +81,5 @@ data DsMetaVal
 -- | Desugaring monad. See also 'TcM'.
 type DsM = TcRnIf DsGblEnv DsLclEnv
 
+-- See Note [The Decoupling Abstract Data Hack]
+type instance DsForeignsHook = [LForeignDecl GhcTc] -> DsM (ForeignStubs, OrdList (Id, CoreExpr))



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9280042ca55ccd66d3e419e41e62a2bd2e28bd6f

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/9280042ca55ccd66d3e419e41e62a2bd2e28bd6f
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20200910/ed30abc6/attachment-0001.html>


More information about the ghc-commits mailing list