|
4 | 4 | {-# LANGUAGE CPP #-} |
5 | 5 | {-# LANGUAGE DuplicateRecordFields #-} |
6 | 6 | {-# LANGUAGE TypeFamilies #-} |
| 7 | +{-# LANGUAGE PartialTypeSignatures #-} |
7 | 8 |
|
8 | 9 | -- | A Shake implementation of the compiler service, built |
9 | 10 | -- using the "Shaker" abstraction layer for in-memory use. |
@@ -93,7 +94,7 @@ import Data.Proxy |
93 | 94 | import qualified Data.Text as T |
94 | 95 | import qualified Data.Text.Encoding as T |
95 | 96 | import qualified Data.Text.Utf16.Rope.Mixed as Rope |
96 | | -import Data.Time (UTCTime (..)) |
| 97 | +import Data.Time (UTCTime (..), getCurrentTime, diffUTCTime) |
97 | 98 | import Data.Time.Clock.POSIX (posixSecondsToUTCTime) |
98 | 99 | import Data.Tuple.Extra |
99 | 100 | import Data.Typeable (cast) |
@@ -175,6 +176,12 @@ import System.Info.Extra (isWindows) |
175 | 176 |
|
176 | 177 | import qualified Data.IntMap as IM |
177 | 178 | import GHC.Fingerprint |
| 179 | +import Text.Pretty.Simple |
| 180 | +import qualified Data.Map.Strict as Map |
| 181 | +import System.FilePath (takeExtension, takeFileName, normalise, dropTrailingPathSeparator, dropExtension, splitDirectories) |
| 182 | +import Data.Char (isUpper) |
| 183 | +import System.Directory.Extra (listFilesRecursive, listFilesInside) |
| 184 | +import System.IO.Unsafe |
178 | 185 |
|
179 | 186 | data Log |
180 | 187 | = LogShake Shake.Log |
@@ -319,30 +326,21 @@ getParsedModuleDefinition packageState opt file ms = do |
319 | 326 | getLocatedImportsRule :: Recorder (WithPriority Log) -> Rules () |
320 | 327 | getLocatedImportsRule recorder = |
321 | 328 | define (cmapWithPrio LogShake recorder) $ \GetLocatedImports file -> do |
| 329 | + |
322 | 330 | ModSummaryResult{msrModSummary = ms} <- use_ GetModSummaryWithoutTimestamps file |
323 | | - (KnownTargets targets targetsMap) <- useNoFile_ GetKnownTargets |
| 331 | + -- TODO: should we reverse this concatenation, there are way less |
| 332 | + -- source import than normal import in theory, so it should be faster |
324 | 333 | let imports = [(False, imp) | imp <- ms_textual_imps ms] ++ [(True, imp) | imp <- ms_srcimps ms] |
325 | 334 | env_eq <- use_ GhcSession file |
326 | 335 | let env = hscEnv env_eq |
327 | 336 | let import_dirs = map (second homeUnitEnv_dflags) $ hugElts $ hsc_HUG env |
328 | 337 | let dflags = hsc_dflags env |
329 | 338 | opt <- getIdeOptions |
330 | | - let getTargetFor modName nfp |
331 | | - | Just (TargetFile nfp') <- HM.lookup (TargetFile nfp) targetsMap = do |
332 | | - -- reuse the existing NormalizedFilePath in order to maximize sharing |
333 | | - itExists <- getFileExists nfp' |
334 | | - return $ if itExists then Just nfp' else Nothing |
335 | | - | Just tt <- HM.lookup (TargetModule modName) targets = do |
336 | | - -- reuse the existing NormalizedFilePath in order to maximize sharing |
337 | | - let ttmap = HM.mapWithKey const (HashSet.toMap tt) |
338 | | - nfp' = HM.lookupDefault nfp nfp ttmap |
339 | | - itExists <- getFileExists nfp' |
340 | | - return $ if itExists then Just nfp' else Nothing |
341 | | - | otherwise = do |
342 | | - itExists <- getFileExists nfp |
343 | | - return $ if itExists then Just nfp else Nothing |
| 339 | + |
| 340 | + moduleMaps <- use_ GetModulesPaths file |
344 | 341 | (diags, imports') <- fmap unzip $ forM imports $ \(isSource, (mbPkgName, modName)) -> do |
345 | | - diagOrImp <- locateModule (hscSetFlags dflags env) import_dirs (optExtensions opt) getTargetFor modName mbPkgName isSource |
| 342 | + |
| 343 | + diagOrImp <- locateModule moduleMaps (hscSetFlags dflags env) import_dirs (optExtensions opt) modName mbPkgName isSource |
346 | 344 | case diagOrImp of |
347 | 345 | Left diags -> pure (diags, Just (modName, Nothing)) |
348 | 346 | Right (FileImport path) -> pure ([], Just (modName, Just path)) |
@@ -632,10 +630,51 @@ getModuleGraphRule recorder = defineEarlyCutOffNoFile (cmapWithPrio LogShake rec |
632 | 630 | fs <- toKnownFiles <$> useNoFile_ GetKnownTargets |
633 | 631 | dependencyInfoForFiles (HashSet.toList fs) |
634 | 632 |
|
| 633 | +{-# NOINLINE cacheVar #-} |
| 634 | +cacheVar = unsafePerformIO (newTVarIO mempty) |
| 635 | + |
| 636 | +getModulesPathsRule :: Recorder (WithPriority Log) -> Rules () |
| 637 | +getModulesPathsRule recorder = defineEarlyCutoff (cmapWithPrio LogShake recorder) $ Rule $ \GetModulesPaths file -> do |
| 638 | + env_eq <- use_ GhcSession file |
| 639 | + |
| 640 | + cache <- liftIO (readTVarIO cacheVar) |
| 641 | + case Map.lookup (envUnique env_eq) cache of |
| 642 | + Just res -> pure (mempty, ([], Just res)) |
| 643 | + Nothing -> do |
| 644 | + let env = hscEnv env_eq |
| 645 | + let import_dirs = map (second homeUnitEnv_dflags) $ hugElts $ hsc_HUG env |
| 646 | + opt <- getIdeOptions |
| 647 | + let exts = (optExtensions opt) |
| 648 | + let acceptedExtensions = concatMap (\x -> ['.':x, '.':x <> "-boot"]) exts |
| 649 | + |
| 650 | + (unzip -> (a, b)) <- flip mapM import_dirs $ \(u, dyn) -> do |
| 651 | + (unzip -> (a, b)) <- flip mapM (importPaths dyn) $ \dir' -> do |
| 652 | + let dir = dropTrailingPathSeparator dir' |
| 653 | + let predicate path = pure (path == dir || isUpper (head (takeFileName path))) |
| 654 | + let dir_number_directories = length (splitDirectories dir) |
| 655 | + let toModule file = mkModuleName (intercalate "." $ drop dir_number_directories (splitDirectories (dropExtension file))) |
| 656 | + |
| 657 | + -- TODO: we are taking/droping extension, this could be factorized to save a few cpu cycles ;) |
| 658 | + -- TODO: do acceptedextensions needs to be a set ? or a vector? |
| 659 | + modules <- fmap (\path -> (toModule path, toNormalizedFilePath' path)) . filter (\y -> takeExtension y `elem` acceptedExtensions) <$> liftIO (listFilesInside predicate dir) |
| 660 | + let isSourceModule (_, path) = "-boot" `isSuffixOf` fromNormalizedFilePath path |
| 661 | + let (sourceModules, notSourceModules) = partition isSourceModule modules |
| 662 | + pure $ (Map.fromList notSourceModules, Map.fromList sourceModules) |
| 663 | + pure (fmap (u,) $ mconcat a, fmap (u, ) $ mconcat b) |
| 664 | + |
| 665 | + let res = (mconcat a, mconcat b) |
| 666 | + liftIO $ atomically $ modifyTVar' cacheVar (Map.insert (envUnique env_eq) res) |
| 667 | + |
| 668 | + pure (mempty, ([], Just $ (mconcat a, mconcat b))) |
| 669 | + |
635 | 670 | dependencyInfoForFiles :: [NormalizedFilePath] -> Action (BS.ByteString, DependencyInformation) |
636 | 671 | dependencyInfoForFiles fs = do |
| 672 | + -- liftIO $ print ("fs length", length fs) |
637 | 673 | (rawDepInfo, bm) <- rawDependencyInformation fs |
| 674 | + -- liftIO $ print ("ok with raw deps") |
| 675 | + -- liftIO $ pPrint rawDepInfo |
638 | 676 | let (all_fs, _all_ids) = unzip $ HM.toList $ pathToIdMap $ rawPathIdMap rawDepInfo |
| 677 | + -- liftIO $ print ("all_fs length", length all_fs) |
639 | 678 | msrs <- uses GetModSummaryWithoutTimestamps all_fs |
640 | 679 | let mss = map (fmap msrModSummary) msrs |
641 | 680 | let deps = map (\i -> IM.lookup (getFilePathId i) (rawImports rawDepInfo)) _all_ids |
@@ -714,6 +753,7 @@ loadGhcSession recorder ghcSessionDepsConfig = do |
714 | 753 | IdeGhcSession{loadSessionFun} <- useNoFile_ GhcSessionIO |
715 | 754 | -- loading is always returning a absolute path now |
716 | 755 | (val,deps) <- liftIO $ loadSessionFun $ fromNormalizedFilePath file |
| 756 | + -- TODO: this is responsible for a LOT of allocations |
717 | 757 |
|
718 | 758 | -- add the deps to the Shake graph |
719 | 759 | let addDependency fp = do |
@@ -1235,6 +1275,7 @@ mainRule recorder RulesConfig{..} = do |
1235 | 1275 | getModIfaceRule recorder |
1236 | 1276 | getModSummaryRule templateHaskellWarning recorder |
1237 | 1277 | getModuleGraphRule recorder |
| 1278 | + getModulesPathsRule recorder |
1238 | 1279 | getFileHashRule recorder |
1239 | 1280 | knownFilesRule recorder |
1240 | 1281 | getClientSettingsRule recorder |
|
0 commit comments