Skip to content
Draft
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
6 changes: 4 additions & 2 deletions flake.nix
Original file line number Diff line number Diff line change
Expand Up @@ -60,7 +60,7 @@
chmod +x $dest
'';

mkDevShell = hpkgs: with pkgs; mkShell {
mkDevShell = hpkgs: with pkgs; pkgs.mkShell {
name = "haskell-language-server-dev-ghc${hpkgs.ghc.version}";
# For binary Haskell tools, we use the default Nixpkgs GHC version.
# This removes a rebuild with a different GHC version. The drawback of
Expand Down Expand Up @@ -106,7 +106,9 @@
in {
# Developement shell with only dev tools
devShells = {
default = mkDevShell pkgs.haskellPackages;
default = pkgs.mkShell {
buildInputs = with pkgs; [zlib haskell.compiler.ghc910 cabal-install];
};
shell-ghc96 = mkDevShell pkgs.haskell.packages.ghc96;
shell-ghc98 = mkDevShell pkgs.haskell.packages.ghc98;
shell-ghc910 = mkDevShell pkgs.haskell.packages.ghc910;
Expand Down
1 change: 1 addition & 0 deletions ghcide-test/exe/CompletionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -32,6 +32,7 @@ import Test.Hls.FileSystem (file, text)
import Test.Hls.Util
import Test.Tasty
import Test.Tasty.HUnit
import Debug.Pretty.Simple

tests :: TestTree
tests
Expand Down
1 change: 1 addition & 0 deletions ghcide/ghcide.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -107,6 +107,7 @@ library
, unliftio-core
, unordered-containers >=0.2.10.0
, vector
, pretty-simple

if os(windows)
build-depends: Win32
Expand Down
6 changes: 4 additions & 2 deletions ghcide/session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -476,8 +476,9 @@
-- If we don't generate a TargetFile for each potential location, we will only have
-- 'TargetFile Foo.hs' in the 'knownTargetsVar', thus not find 'TargetFile Foo.hs-boot'
-- and also not find 'TargetModule Foo'.
fs <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
pure $ map (\fp -> (TargetFile fp, Set.singleton fp)) (nubOrd (f:fs))
pure $ do
file <- nubOrd (f:targetLocations)
pure $ (TargetFile file, Set.singleton file)

Check warning on line 481 in ghcide/session-loader/Development/IDE/Session.hs

View workflow job for this annotation

GitHub Actions / Hlint check run

Suggestion in loadSessionWithOptions in module Development.IDE.Session: Redundant $ ▫︎ Found: "pure $ (TargetFile file, Set.singleton file)" ▫︎ Perhaps: "pure (TargetFile file, Set.singleton file)"
TargetModule _ -> do
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
return [(targetTarget, Set.fromList found)]
Expand Down Expand Up @@ -629,7 +630,7 @@
[] -> error $ "GHC version could not be parsed: " <> version
((runTime, _):_)
| compileTime == runTime -> do
atomicModifyIORef' cradle_files (\xs -> (cfp:xs,()))

Check warning on line 633 in ghcide/session-loader/Development/IDE/Session.hs

View workflow job for this annotation

GitHub Actions / Hlint check run

Warning in loadSessionWithOptions in module Development.IDE.Session: Use atomicModifyIORef'_ ▫︎ Found: "atomicModifyIORef' cradle_files (\\ xs -> (cfp : xs, ()))" ▫︎ Perhaps: "atomicModifyIORef'_ cradle_files ((:) cfp)"
session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
| otherwise -> return (([renderPackageSetupException cfp GhcVersionMismatch{..}], Nothing),[])
-- Failure case, either a cradle error or the none cradle
Expand Down Expand Up @@ -764,6 +765,7 @@
targetDepends :: !DependencyInfo,
targetLocations :: ![NormalizedFilePath]
}
deriving (Show)

fromTargetId :: [FilePath] -- ^ import paths
-> [String] -- ^ extensions to consider
Expand Down Expand Up @@ -896,7 +898,7 @@
x <- map errMsgDiagnostic closure_errs
DriverHomePackagesNotClosed us <- pure x
pure us
isBad ci = (homeUnitId_ (componentDynFlags ci)) `OS.member` bad_units

Check warning on line 901 in ghcide/session-loader/Development/IDE/Session.hs

View workflow job for this annotation

GitHub Actions / Hlint check run

Suggestion in newComponentCache in module Development.IDE.Session: Redundant bracket ▫︎ Found: "(homeUnitId_ (componentDynFlags ci)) `OS.member` bad_units" ▫︎ Perhaps: "homeUnitId_ (componentDynFlags ci) `OS.member` bad_units"
-- Whenever we spin up a session on Linux, dynamically load libm.so.6
-- in. We need this in case the binary is statically linked, in which
-- case the interactive session will fail when trying to load
Expand Down
10 changes: 10 additions & 0 deletions ghcide/src/Development/IDE/Core/RuleTypes.hs
Original file line number Diff line number Diff line change
Expand Up @@ -412,6 +412,9 @@ type instance RuleResult GetModSummary = ModSummaryResult
-- | Generate a ModSummary with the timestamps and preprocessed content elided, for more successful early cutoff
type instance RuleResult GetModSummaryWithoutTimestamps = ModSummaryResult

type instance RuleResult GetModulesPaths = (M.Map ModuleName (UnitId, NormalizedFilePath),
M.Map ModuleName (UnitId, NormalizedFilePath))

data GetParsedModule = GetParsedModule
deriving (Eq, Show, Generic)
instance Hashable GetParsedModule
Expand Down Expand Up @@ -524,6 +527,13 @@ data GetModSummaryWithoutTimestamps = GetModSummaryWithoutTimestamps
instance Hashable GetModSummaryWithoutTimestamps
instance NFData GetModSummaryWithoutTimestamps

-- | Scan all the import directory for existing modules and build a map from
-- module name to paths
data GetModulesPaths = GetModulesPaths
deriving (Eq, Show, Generic)
instance Hashable GetModulesPaths
instance NFData GetModulesPaths

data GetModSummary = GetModSummary
deriving (Eq, Show, Generic)
instance Hashable GetModSummary
Expand Down
129 changes: 113 additions & 16 deletions ghcide/src/Development/IDE/Core/Rules.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,6 +4,7 @@
{-# LANGUAGE CPP #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE PartialTypeSignatures #-}

-- | A Shake implementation of the compiler service, built
-- using the "Shaker" abstraction layer for in-memory use.
Expand Down Expand Up @@ -55,6 +56,7 @@ module Development.IDE.Core.Rules(
GhcSessionDepsConfig(..),
Log(..),
DisplayTHWarning(..),
extendModuleMapWithKnownTargets,
) where

import Control.Applicative
Expand Down Expand Up @@ -175,6 +177,10 @@ import System.Info.Extra (isWindows)

import qualified Data.IntMap as IM
import GHC.Fingerprint
import qualified Data.Map.Strict as Map
import System.FilePath (takeExtension, takeFileName, normalise, dropExtension, splitDirectories)
import Data.Char (isUpper)
import System.Directory.Extra (listFilesInside)

data Log
= LogShake Shake.Log
Expand Down Expand Up @@ -313,30 +319,22 @@ getParsedModuleDefinition packageState opt file ms = do
getLocatedImportsRule :: Recorder (WithPriority Log) -> Rules ()
getLocatedImportsRule recorder =
define (cmapWithPrio LogShake recorder) $ \GetLocatedImports file -> do

ModSummaryResult{msrModSummary = ms} <- use_ GetModSummaryWithoutTimestamps file
(KnownTargets targets targetsMap) <- useNoFile_ GetKnownTargets
-- TODO: should we reverse this concatenation, there are way less
-- source import than normal import in theory, so it should be faster
let imports = [(False, imp) | imp <- ms_textual_imps ms] ++ [(True, imp) | imp <- ms_srcimps ms]
env_eq <- use_ GhcSession file
let env = hscEnv env_eq
let import_dirs = map (second homeUnitEnv_dflags) $ hugElts $ hsc_HUG env
let dflags = hsc_dflags env
opt <- getIdeOptions
let getTargetFor modName nfp
| Just (TargetFile nfp') <- HM.lookup (TargetFile nfp) targetsMap = do
-- reuse the existing NormalizedFilePath in order to maximize sharing
itExists <- getFileExists nfp'
return $ if itExists then Just nfp' else Nothing
| Just tt <- HM.lookup (TargetModule modName) targets = do
-- reuse the existing NormalizedFilePath in order to maximize sharing
let ttmap = HM.mapWithKey const (HashSet.toMap tt)
nfp' = HM.lookupDefault nfp nfp ttmap
itExists <- getFileExists nfp'
return $ if itExists then Just nfp' else Nothing
| otherwise = do
itExists <- getFileExists nfp
return $ if itExists then Just nfp else Nothing

moduleMaps <- extendModuleMapWithKnownTargets file

(diags, imports') <- fmap unzip $ forM imports $ \(isSource, (mbPkgName, modName)) -> do
diagOrImp <- locateModule (hscSetFlags dflags env) import_dirs (optExtensions opt) getTargetFor modName mbPkgName isSource

diagOrImp <- locateModule moduleMaps (hscSetFlags dflags env) import_dirs (optExtensions opt) modName mbPkgName isSource
case diagOrImp of
Left diags -> pure (diags, Just (modName, Nothing))
Right (FileImport path) -> pure ([], Just (modName, Just path))
Expand Down Expand Up @@ -626,6 +624,103 @@ getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake rec
fs <- toKnownFiles <$> useNoFile_ GetKnownTargets
dependencyInfoForFiles (HashSet.toList fs)

getModulesPathsRule :: Recorder (WithPriority Log) -> Rules ()
getModulesPathsRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModulesPaths file -> do
env_eq <- use_ GhcSession file

ShakeExtras{moduleToPathCache} <- getShakeExtras

cache <- liftIO (readTVarIO moduleToPathCache)
case Map.lookup (envUnique env_eq) cache of
Just res -> pure (mempty, ([], Just res))
Nothing -> do
let env = hscEnv env_eq
let import_dirs = map (second homeUnitEnv_dflags) $ hugElts $ hsc_HUG env
opt <- getIdeOptions
let exts = (optExtensions opt)
let acceptedExtensions = concatMap (\x -> ['.':x, '.':x <> "-boot"]) exts

(unzip -> (a, b)) <- flip mapM import_dirs $ \(u, dyn) -> do
(unzip -> (a, b)) <- flip mapM (importPaths dyn) $ \dir' -> do
let dir = normalise dir'
let predicate path = pure (normalise path == dir || case takeFileName path of
[] -> False
(x:_) -> isUpper x)
let dir_number_directories = length (splitDirectories dir)
let toModule file = mkModuleName (intercalate "." $ drop dir_number_directories (splitDirectories (dropExtension file)))

-- TODO: we are taking/dropping extension, this could be factorized to save a few cpu cycles ;)
-- TODO: do acceptedextensions needs to be a set ? or a vector?
-- If the directory is empty, we return an empty list of modules
-- using 'catch' instead of an exception which would kill the LSP
modules <- (fmap (\path -> (toModule path, toNormalizedFilePath' path)) . filter (\y -> takeExtension y `elem` acceptedExtensions) <$> liftIO (listFilesInside predicate dir))
`catch` (\(_ :: IOException) -> pure [])
let isSourceModule (_, path) = "-boot" `isSuffixOf` fromNormalizedFilePath path
let (sourceModules, notSourceModules) = partition isSourceModule modules
pure $ (Map.fromList notSourceModules, Map.fromList sourceModules)
pure (fmap (u,) $ mconcat a, fmap (u, ) $ mconcat b)

let res = (mconcat a, mconcat b)
liftIO $ atomically $ modifyTVar' moduleToPathCache (Map.insert (envUnique env_eq) res)

pure (mempty, ([], Just res))

-- | Extend the map from module name to filepath (exiting on the drive) with
-- the list of known targets provided by HLS
--
-- These known targets are files which were recently created and not yet saved
-- to the filesystem.
--
-- TODO: for now the implementation is O(number_of_known_files *
-- number_of_include_path) which is inacceptable and should be addressed.
extendModuleMapWithKnownTargets
:: NormalizedFilePath
-> Action (Map.Map ModuleName (UnitId, NormalizedFilePath), Map.Map ModuleName (UnitId, NormalizedFilePath))
extendModuleMapWithKnownTargets file = do
(notSourceModules, sourceModules) <- use_ GetModulesPaths file
KnownTargets targetsMap <- useNoFile_ GetKnownTargets

env_eq <- use_ GhcSession file
let env = hscEnv env_eq
let import_dirs = map (second homeUnitEnv_dflags) $ hugElts $ hsc_HUG env
opt <- getIdeOptions
let exts = (optExtensions opt)
let acceptedExtensions = concatMap (\x -> ['.':x, '.':x <> "-boot"]) exts

let (unzip -> (catMaybes -> a, catMaybes -> b)) = do
(u, dyn) <- import_dirs
-- TODO: avoid using so much `FilePath` logic AND please please,
-- normalize earlier.
--
-- The normalise here is in order to remove the trailing `.` which
-- could break the comparison later.
(normalise -> dir') <- importPaths dyn
let dirComponents = splitDirectories dir'
let dir_number_directories = length dirComponents
-- TODO: the _target may represents something different than the path
-- stored in paths. This need to be investigated.
(_target, paths) <- HM.toList targetsMap
path <- HashSet.toList paths
let pathString = fromNormalizedFilePath path
let pathComponents = splitDirectories pathString

-- Ensure this file is in the directory
guard $ dirComponents `isPrefixOf` pathComponents

-- Ensure that this extension is accepted
guard $ takeExtension pathString `elem` acceptedExtensions
let modName = mkModuleName (intercalate "." $ drop dir_number_directories (splitDirectories (dropExtension pathString)))
let isSourceModule = "-boot" `isSuffixOf` pathString
if isSourceModule
then
pure (Nothing, Just (modName, (u, path)))
else
pure (Just (modName, (u, path)), Nothing)


pure $ (Map.fromList a <> notSourceModules, Map.fromList b <> sourceModules)


dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation)
dependencyInfoForFiles fs = do
(rawDepInfo, bm) <- rawDependencyInformation fs
Expand Down Expand Up @@ -708,6 +803,7 @@ loadGhcSession recorder ghcSessionDepsConfig = do
IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO
-- loading is always returning a absolute path now
(val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file
-- TODO: this is responsible for a LOT of allocations

-- add the deps to the Shake graph
let addDependency fp = do
Expand Down Expand Up @@ -1229,6 +1325,7 @@ mainRule recorder RulesConfig{..} = do
getModIfaceRule recorder
getModSummaryRule templateHaskellWarning recorder
getModuleGraphRule recorder
getModulesPathsRule recorder
getFileHashRule recorder
knownFilesRule recorder
getClientSettingsRule recorder
Expand Down
11 changes: 10 additions & 1 deletion ghcide/src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -135,7 +135,7 @@ import Development.IDE.Core.WorkerThread
import Development.IDE.GHC.Compat (NameCache,
NameCacheUpdater,
initNameCache,
knownKeyNames)
knownKeyNames, ModuleName, UnitId)
import Development.IDE.GHC.Orphans ()
import Development.IDE.Graph hiding (ShakeValue,
action)
Expand Down Expand Up @@ -178,6 +178,7 @@ import System.FilePath hiding (makeRelative)
import System.IO.Unsafe (unsafePerformIO)
import System.Time.Extra
import UnliftIO (MonadUnliftIO (withRunInIO))
import Data.Map.Strict (Map)


data Log
Expand Down Expand Up @@ -310,6 +311,10 @@ data ShakeExtras = ShakeExtras
,ideNc :: NameCache
-- | A mapping of module name to known target (or candidate targets, if missing)
,knownTargetsVar :: TVar (Hashed KnownTargets)
,moduleToPathCache :: TVar (Map
Unique
(Map ModuleName (UnitId, NormalizedFilePath),
Map ModuleName (UnitId, NormalizedFilePath)))
-- | A mapping of exported identifiers for local modules. Updated on kick
,exportsMap :: TVar ExportsMap
-- | A work queue for actions added via 'runInShakeSession'
Expand Down Expand Up @@ -704,6 +709,8 @@ shakeOpen recorder lspEnv defaultConfig idePlugins debouncer
dirtyKeys <- newTVarIO mempty
-- Take one VFS snapshot at the start
vfsVar <- newTVarIO =<< vfsSnapshot lspEnv

moduleToPathCache <- newTVarIO mempty
pure ShakeExtras{shakeRecorder = recorder, ..}
shakeDb <-
shakeNewDatabase
Expand Down Expand Up @@ -1481,3 +1488,5 @@ runWithSignal msgStart msgEnd files rule = do
kickSignal testing lspEnv files msgStart
void $ uses rule files
kickSignal testing lspEnv files msgEnd


Loading
Loading