Skip to content

Commit

Permalink
Add GHC 9.2 support for hie-compat (#2003)
Browse files Browse the repository at this point in the history
* Add GHC 9.2 support hie-compat

* Remove mkHieFile from public API

Then we can share the module re-exports for GHC >= 9
  • Loading branch information
fendor committed Jul 26, 2021
1 parent 9207050 commit 5ddc93a
Show file tree
Hide file tree
Showing 11 changed files with 15 additions and 128 deletions.
3 changes: 1 addition & 2 deletions ghcide/src/Development/IDE/GHC/Compat.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,6 @@ module Development.IDE.GHC.Compat(
HieFile(..),
NameCacheUpdater(..),
hieExportNames,
mkHieFile,
mkHieFile',
enrichHie,
writeHieFile,
Expand Down Expand Up @@ -159,7 +158,7 @@ import Module (InstalledUnitId,
toInstalledUnitId)
import TcType (pprSigmaType)
#endif
import Compat.HieAst (enrichHie, mkHieFile)
import Compat.HieAst (enrichHie)
import Compat.HieBin
import Compat.HieTypes
import Compat.HieUtils
Expand Down
7 changes: 6 additions & 1 deletion hie-compat/hie-compat.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -30,6 +30,8 @@ library
build-depends: ghc, ghc-boot
if (impl(ghc >= 9.0) && impl(ghc < 9.1))
ghc-options: -Wall -Wno-name-shadowing
else
ghc-options: -Wall -Wno-name-shadowing

exposed-modules:
Compat.HieAst
Expand All @@ -45,5 +47,8 @@ library
if (impl(ghc > 8.9) && impl(ghc < 8.11))
hs-source-dirs: src-ghc810 src-reexport
if (impl(ghc >= 9.0) && impl(ghc < 9.1) || flag(ghc-lib))
hs-source-dirs: src-ghc901
hs-source-dirs: src-reexport-ghc9
if (impl(ghc >= 9.2) && impl(ghc < 9.3))
hs-source-dirs: src-reexport-ghc9


33 changes: 2 additions & 31 deletions hie-compat/src-ghc810/Compat/HieAst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ Main functions for .hie file generation
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Compat.HieAst ( mkHieFile, enrichHie ) where
module Compat.HieAst ( enrichHie ) where

import GhcPrelude

Expand All @@ -32,7 +32,7 @@ import Desugar ( deSugarExpr )
import FieldLabel
import GHC.Hs
import HscTypes
import Module ( ModuleName, ml_hs_file )
import Module ( ModuleName )
import MonadUtils ( concatMapM, liftIO )
import Name ( Name, nameSrcSpan )
import NameEnv ( NameEnv, emptyNameEnv, extendNameEnv, lookupNameEnv )
Expand All @@ -41,15 +41,11 @@ import TcHsSyn ( hsLitType, hsPatType )
import Type ( mkVisFunTys, Type )
import TysWiredIn ( mkListTy, mkSumTy )
import Var ( Id, Var, setVarName, varName, varType )
import TcRnTypes
import MkIface ( mkIfaceExports )
import Panic

import HieTypes
import HieUtils

import qualified Data.Array as A
import qualified Data.ByteString as BS
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Data ( Data, Typeable )
Expand Down Expand Up @@ -223,31 +219,6 @@ modifyState = foldr go id

type HieM = ReaderT HieState Hsc

-- | Construct an 'HieFile' from the outputs of the typechecker.
mkHieFile :: ModSummary
-> TcGblEnv
-> RenamedSource
-> BS.ByteString -> Hsc HieFile
mkHieFile ms ts rs src = do
let tc_binds = tcg_binds ts
(asts', arr) <- getCompressedAsts tc_binds rs
let Just src_file = ml_hs_file $ ms_location ms
return $ HieFile
{ hie_hs_file = src_file
, hie_module = ms_mod ms
, hie_types = arr
, hie_asts = asts'
-- mkIfaceExports sorts the AvailInfos for stability
, hie_exports = mkIfaceExports (tcg_exports ts)
, hie_hs_src = src
}

getCompressedAsts :: TypecheckedSource -> RenamedSource
-> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
getCompressedAsts ts rs = do
asts <- enrichHie ts rs
return $ compressTypes asts

enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
Expand Down
34 changes: 2 additions & 32 deletions hie-compat/src-ghc86/Compat/HieAst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -17,7 +17,7 @@ Main functions for .hie file generation
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DataKinds #-}
module Compat.HieAst ( mkHieFile, enrichHie ) where
module Compat.HieAst ( enrichHie ) where

import Avail ( Avails )
import Bag ( Bag, bagToList )
Expand All @@ -30,22 +30,18 @@ import Desugar ( deSugarExpr )
import FieldLabel
import HsSyn
import HscTypes
import Module ( ModuleName, ml_hs_file )
import Module ( ModuleName )
import MonadUtils ( concatMapM, liftIO )
import Name ( Name, nameSrcSpan )
import SrcLoc
import TcHsSyn ( hsLitType, hsPatType )
import Type ( mkFunTys, Type )
import TysWiredIn ( mkListTy, mkSumTy )
import Var ( Id, Var, setVarName, varName, varType )
import TcRnTypes
import MkIface ( mkIfaceExports )

import Compat.HieTypes
import Compat.HieUtils

import qualified Data.Array as A
import qualified Data.ByteString as BS
import qualified Data.Map as M
import qualified Data.Set as S
import Data.Data ( Data, Typeable )
Expand Down Expand Up @@ -101,32 +97,6 @@ modifyState = foldr go id

type HieM = ReaderT HieState Hsc

-- | Construct an 'HieFile' from the outputs of the typechecker.
mkHieFile :: ModSummary
-> TcGblEnv
-> RenamedSource
-> BS.ByteString
-> Hsc HieFile
mkHieFile ms ts rs src = do
let tc_binds = tcg_binds ts
(asts', arr) <- getCompressedAsts tc_binds rs
let Just src_file = ml_hs_file $ ms_location ms
return $ HieFile
{ hie_hs_file = src_file
, hie_module = ms_mod ms
, hie_types = arr
, hie_asts = asts'
-- mkIfaceExports sorts the AvailInfos for stability
, hie_exports = mkIfaceExports (tcg_exports ts)
, hie_hs_src = src
}

getCompressedAsts :: TypecheckedSource -> RenamedSource
-> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
getCompressedAsts ts rs = do
asts <- enrichHie ts rs
return $ compressTypes asts

enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
Expand Down
28 changes: 1 addition & 27 deletions hie-compat/src-ghc88/Compat/HieAst.hs
Original file line number Diff line number Diff line change
Expand Up @@ -16,7 +16,7 @@ Main functions for .hie file generation
{-# LANGUAGE AllowAmbiguousTypes #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Compat.HieAst ( mkHieFile, enrichHie ) where
module Compat.HieAst ( enrichHie ) where

import Avail ( Avails )
import Bag ( Bag, bagToList )
Expand Down Expand Up @@ -90,32 +90,6 @@ modifyState = foldr go id

type HieM = ReaderT HieState Hsc

-- | Construct an 'HieFile' from the outputs of the typechecker.
mkHieFile :: ModSummary
-> TcGblEnv
-> RenamedSource
-> BS.ByteString
-> Hsc HieFile
mkHieFile ms ts rs src = do
let tc_binds = tcg_binds ts
(asts', arr) <- getCompressedAsts tc_binds rs
let Just src_file = ml_hs_file $ ms_location ms
return $ HieFile
{ hie_hs_file = src_file
, hie_module = ms_mod ms
, hie_types = arr
, hie_asts = asts'
-- mkIfaceExports sorts the AvailInfos for stability
, hie_exports = mkIfaceExports (tcg_exports ts)
, hie_hs_src = src
}

getCompressedAsts :: TypecheckedSource -> RenamedSource
-> Hsc (HieASTs TypeIndex, A.Array TypeIndex HieTypeFlat)
getCompressedAsts ts rs = do
asts <- enrichHie ts rs
return $ compressTypes asts

enrichHie :: TypecheckedSource -> RenamedSource -> Hsc (HieASTs Type)
enrichHie ts (hsGrp, imports, exports, _) = flip runReaderT initState $ do
tasts <- toHie $ fmap (BC RegularBind ModuleScope) ts
Expand Down
35 changes: 0 additions & 35 deletions hie-compat/src-ghc901/Compat/HieAst.hs

This file was deleted.

3 changes: 3 additions & 0 deletions hie-compat/src-reexport-ghc9/Compat/HieAst.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,3 @@
module Compat.HieAst ( enrichHie ) where

import GHC.Iface.Ext.Ast (enrichHie)
File renamed without changes.
File renamed without changes.
File renamed without changes.
File renamed without changes.

0 comments on commit 5ddc93a

Please sign in to comment.