Skip to content

Commit

Permalink
lose the ghc-lib flag (#1366)
Browse files Browse the repository at this point in the history
Co-authored-by: wz1000 <zubin.duggal@gmail.com>
Co-authored-by: mergify[bot] <37929162+mergify[bot]@users.noreply.github.com>
  • Loading branch information
3 people committed Feb 16, 2021
1 parent 192cd82 commit f73b936
Show file tree
Hide file tree
Showing 5 changed files with 18 additions and 79 deletions.
36 changes: 4 additions & 32 deletions ghcide/ghcide.cabal
Expand Up @@ -27,11 +27,6 @@ source-repository head
type: git
location: https://github.com/haskell/ghcide.git

flag ghc-lib
description: build against ghc-lib instead of the ghc package
default: False
manual: True

library
default-language: Haskell2010
build-depends:
Expand Down Expand Up @@ -92,19 +87,10 @@ library
opentelemetry >=0.6.1,
heapsize ==0.3.*,
unliftio,
unliftio-core
if flag(ghc-lib)
build-depends:
ghc-lib >= 8.8,
ghc-lib-parser >= 8.8
cpp-options: -DGHC_LIB
else
build-depends:
unliftio-core,
ghc-boot-th,
ghc-boot,
ghc >= 8.6,
-- These dependencies are used by Development.IDE.Session and are
-- Haskell specific. So don't use them when building with -fghc-lib!
ghc-check >=0.5.0.1,
ghc-paths,
cryptohash-sha1 >=0.11.100 && <0.12,
Expand Down Expand Up @@ -141,6 +127,7 @@ library

hs-source-dirs:
src
session-loader
include-dirs:
include
exposed-modules:
Expand Down Expand Up @@ -169,6 +156,7 @@ library
Development.IDE.LSP.LanguageServer
Development.IDE.LSP.Outline
Development.IDE.LSP.Server
Development.IDE.Session
Development.IDE.Spans.Common
Development.IDE.Spans.Documentation
Development.IDE.Spans.AtPoint
Expand All @@ -191,26 +179,14 @@ library
Development.IDE.Plugin.Test
Development.IDE.Plugin.TypeLenses

-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
-- the real GHC library and the types are incompatible. Furthermore, when
-- building with ghc-lib we need to make this Haskell agnostic, so no
-- hie-bios!
-- We also put these modules into a separate hs-source-dirs so we can avoid
-- compiling them at all if ghc-lib is not set
if !flag(ghc-lib)
hs-source-dirs:
session-loader
exposed-modules:
Development.IDE.Session
other-modules:
Development.IDE.Session.VersionCheck
other-modules:
Development.IDE.Core.FileExists
Development.IDE.GHC.CPP
Development.IDE.GHC.Warnings
Development.IDE.LSP.Notifications
Development.IDE.Plugin.CodeAction.PositionIndexed
Development.IDE.Plugin.Completions.Logic
Development.IDE.Session.VersionCheck
Development.IDE.Types.Action
ghc-options: -Wall -Wno-name-shadowing -Wincomplete-uni-patterns -Wno-unticked-promoted-constructors

Expand Down Expand Up @@ -261,8 +237,6 @@ benchmark benchHist
yaml

executable ghcide
if flag(ghc-lib)
buildable: False
default-language: Haskell2010
include-dirs:
include
Expand Down Expand Up @@ -322,8 +296,6 @@ executable ghcide
ViewPatterns

test-suite ghcide-tests
if flag(ghc-lib)
buildable: False
type: exitcode-stdio-1.0
default-language: Haskell2010
build-tool-depends:
Expand Down
20 changes: 1 addition & 19 deletions ghcide/src/Development/IDE/Core/Rules.hs
Expand Up @@ -633,17 +633,7 @@ getDocMapRule =
(hscEnv -> hsc, _) <- useWithStale_ GhcSessionDeps file
(HAR{refMap=rf}, _) <- useWithStale_ GetHieAst file

-- When possible, rely on the haddocks embedded in our interface files
-- This creates problems on ghc-lib, see comment on 'getDocumentationTryGhc'
#if !defined(GHC_LIB)
let parsedDeps = []
#else
deps <- fromMaybe (TransitiveDependencies [] [] []) <$> use GetDependencies file
let tdeps = transitiveModuleDeps deps
parsedDeps <- uses_ GetParsedModule tdeps
#endif

dkMap <- liftIO $ mkDocMap hsc parsedDeps rf tc
dkMap <- liftIO $ mkDocMap hsc rf tc
return ([],Just dkMap)

-- | Persistent rule to ensure that hover doesn't block on startup
Expand Down Expand Up @@ -921,7 +911,6 @@ generateCoreRule =

getModIfaceRule :: Rules ()
getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
#if !defined(GHC_LIB)
fileOfInterest <- use_ IsFileOfInterest f
res@(_,(_,mhmi)) <- case fileOfInterest of
IsFOI status -> do
Expand All @@ -948,13 +937,6 @@ getModIfaceRule = defineEarlyCutoff $ \GetModIface f -> do
compiledLinkables <- getCompiledLinkables <$> getIdeGlobalAction
liftIO $ modifyVar_ compiledLinkables $ \old -> pure $ extendModuleEnv old mod time
pure res
#else
tm <- use_ TypeCheck f
hsc <- hscEnv <$> use_ GhcSessionDeps f
(diags, !hiFile) <- liftIO $ compileToObjCodeIfNeeded hsc Nothing (error "can't compile with ghc-lib") tm
let fp = hiFileFingerPrint <$> hiFile
return (fp, (diags, hiFile))
#endif

getModIfaceWithoutLinkableRule :: Rules ()
getModIfaceWithoutLinkableRule = defineEarlyCutoff $ \GetModIfaceWithoutLinkable f -> do
Expand Down
14 changes: 1 addition & 13 deletions ghcide/src/Development/IDE/Plugin/Completions.hs
Expand Up @@ -41,9 +41,6 @@ import Control.Concurrent.Async (concurrently)
import GHC.Exts (toList)
import Development.IDE.GHC.Error (rangeToSrcSpan)
import Development.IDE.GHC.Util (prettyPrint)
#if defined(GHC_LIB)
import Development.IDE.Import.DependencyInformation
#endif

descriptor :: PluginId -> PluginDescriptor IdeState
descriptor plId = (defaultPluginDescriptor plId)
Expand All @@ -69,15 +66,6 @@ produceCompletions = do
ms <- fmap fst <$> useWithStale GetModSummaryWithoutTimestamps file
sess <- fmap fst <$> useWithStale GhcSessionDeps file

-- When possible, rely on the haddocks embedded in our interface files
-- This creates problems on ghc-lib, see comment on 'getDocumentationTryGhc'
#if !defined(GHC_LIB)
let parsedDeps = []
#else
deps <- maybe (TransitiveDependencies [] [] []) fst <$> useWithStale GetDependencies file
parsedDeps <- mapMaybe (fmap fst) <$> usesWithStale GetParsedModule (transitiveModuleDeps deps)
#endif

case (ms, sess) of
(Just (ms,imps), Just sess) -> do
let env = hscEnv sess
Expand All @@ -86,7 +74,7 @@ produceCompletions = do
case (global, inScope) of
((_, Just globalEnv), (_, Just inScopeEnv)) -> do
let uri = fromNormalizedUri $ normalizedFilePathToUri file
cdata <- liftIO $ cacheDataProducer uri sess (ms_mod ms) globalEnv inScopeEnv imps parsedDeps
cdata <- liftIO $ cacheDataProducer uri sess (ms_mod ms) globalEnv inScopeEnv imps
return ([], Just cdata)
(_diag, _) ->
return ([], Nothing)
Expand Down
8 changes: 4 additions & 4 deletions ghcide/src/Development/IDE/Plugin/Completions/Logic.hs
Expand Up @@ -294,9 +294,9 @@ mkPragmaCompl label insertText =
Nothing Nothing Nothing Nothing Nothing


cacheDataProducer :: Uri -> HscEnvEq -> Module -> GlobalRdrEnv-> GlobalRdrEnv -> [LImportDecl GhcPs] -> [ParsedModule] -> IO CachedCompletions
cacheDataProducer uri env curMod globalEnv inScopeEnv limports deps = do
let
cacheDataProducer :: Uri -> HscEnvEq -> Module -> GlobalRdrEnv-> GlobalRdrEnv -> [LImportDecl GhcPs] -> IO CachedCompletions
cacheDataProducer uri env curMod globalEnv inScopeEnv limports = do
let
packageState = hscEnv env
curModName = moduleName curMod

Expand Down Expand Up @@ -343,7 +343,7 @@ cacheDataProducer uri env curMod globalEnv inScopeEnv limports deps = do

toCompItem :: Parent -> Module -> ModuleName -> Name -> Maybe (LImportDecl GhcPs) -> IO [CompItem]
toCompItem par m mn n imp' = do
docs <- getDocumentationTryGhc packageState curMod deps n
docs <- getDocumentationTryGhc packageState curMod n
let (mbParent, originName) = case par of
NoParent -> (Nothing, nameOccName n)
ParentIs n' -> (Just $ showNameWithoutUniques n', nameOccName n)
Expand Down
19 changes: 8 additions & 11 deletions ghcide/src/Development/IDE/Spans/Documentation.hs
Expand Up @@ -43,11 +43,10 @@ import HscTypes (HscEnv(hsc_dflags))

mkDocMap
:: HscEnv
-> [ParsedModule]
-> RefMap a
-> TcGblEnv
-> IO DocAndKindMap
mkDocMap env sources rm this_mod =
mkDocMap env rm this_mod =
do let (_ , DeclDocMap this_docs, _) = extractDocs this_mod
d <- foldrM getDocs (mkNameEnv $ M.toList $ fmap (`SpanDocString` SpanDocUris Nothing Nothing) this_docs) names
k <- foldrM getType (tcg_type_env this_mod) names
Expand All @@ -56,7 +55,7 @@ mkDocMap env sources rm this_mod =
getDocs n map
| maybe True (mod ==) $ nameModule_maybe n = pure map -- we already have the docs in this_docs, or they do not exist
| otherwise = do
doc <- getDocumentationTryGhc env mod sources n
doc <- getDocumentationTryGhc env mod n
pure $ extendNameEnv map n doc
getType n map
| isTcOcc $ occName n = do
Expand All @@ -71,23 +70,21 @@ lookupKind :: HscEnv -> Module -> Name -> IO (Maybe TyThing)
lookupKind env mod =
fmap (fromRight Nothing) . catchSrcErrors (hsc_dflags env) "span" . lookupName env mod

getDocumentationTryGhc :: HscEnv -> Module -> [ParsedModule] -> Name -> IO SpanDoc
getDocumentationTryGhc env mod deps n = head <$> getDocumentationsTryGhc env mod deps [n]
getDocumentationTryGhc :: HscEnv -> Module -> Name -> IO SpanDoc
getDocumentationTryGhc env mod n = head <$> getDocumentationsTryGhc env mod [n]

getDocumentationsTryGhc :: HscEnv -> Module -> [ParsedModule] -> [Name] -> IO [SpanDoc]
-- Interfaces are only generated for GHC >= 8.6.
-- In older versions, interface files do not embed Haddocks anyway
getDocumentationsTryGhc env mod sources names = do
getDocumentationsTryGhc :: HscEnv -> Module -> [Name] -> IO [SpanDoc]
getDocumentationsTryGhc env mod names = do
res <- catchSrcErrors (hsc_dflags env) "docs" $ getDocsBatch env mod names
case res of
Left _ -> mapM mkSpanDocText names
Left _ -> return []
Right res -> zipWithM unwrap res names
where
unwrap (Right (Just docs, _)) n = SpanDocString docs <$> getUris n
unwrap _ n = mkSpanDocText n

mkSpanDocText name =
SpanDocText (getDocumentation sources name) <$> getUris name
SpanDocText [] <$> getUris name

-- Get the uris to the documentation and source html pages if they exist
getUris name = do
Expand Down

0 comments on commit f73b936

Please sign in to comment.