[commit: ghc] wip/nfs-locking: Minor revision. (9171856)

git at git.haskell.org git at git.haskell.org
Fri Oct 27 00:05:37 UTC 2017


Repository : ssh://git@git.haskell.org/ghc

On branch  : wip/nfs-locking
Link       : http://ghc.haskell.org/trac/ghc/changeset/9171856f647213aea42005a8dfec9bff0ff7223c/ghc

>---------------------------------------------------------------

commit 9171856f647213aea42005a8dfec9bff0ff7223c
Author: Andrey Mokhov <andrey.mokhov at gmail.com>
Date:   Fri Feb 26 11:37:00 2016 +0000

    Minor revision.
    
    See #210.


>---------------------------------------------------------------

9171856f647213aea42005a8dfec9bff0ff7223c
 src/Oracles/ModuleFiles.hs | 18 ++++++++++++------
 1 file changed, 12 insertions(+), 6 deletions(-)

diff --git a/src/Oracles/ModuleFiles.hs b/src/Oracles/ModuleFiles.hs
index 630a05f..508b554 100644
--- a/src/Oracles/ModuleFiles.hs
+++ b/src/Oracles/ModuleFiles.hs
@@ -34,7 +34,12 @@ determineBuilder file = case takeExtension file of
 --               ".build/stage1/base/build/Prelude.hs"
 -- == Nothing
 findGenerator :: Context -> FilePath -> Action (Maybe (FilePath, Builder))
-findGenerator context file = askOracle $ Generator (context, file)
+findGenerator context file = do
+    maybeSource <- askOracle $ Generator (context, file)
+    return $ do
+        source  <- maybeSource
+        builder <- determineBuilder source
+        return (source, builder)
 
 -- | Find all Haskell source files for a given 'Context'.
 haskellSources :: Context -> Action [FilePath]
@@ -44,8 +49,9 @@ haskellSources context = do
     -- that GHC/Prim.hs lives in build/autogen/. TODO: fix the inconsistency?
     let modFile ("GHC.Prim", _) = autogen -/- "GHC/Prim.hs"
         modFile (m, Nothing   ) = generatedFile context m
-        modFile (m, Just file ) | "//*hs" ?== file = file
-                                | otherwise        = modFile (m, Nothing)
+        modFile (m, Just file )
+            | takeExtension file `elem` [".hs", ".lhs"] = file
+            | otherwise = generatedFile context m
     map modFile <$> contextFiles context
 
 generatedFile :: Context -> String -> FilePath
@@ -53,7 +59,7 @@ generatedFile context moduleName =
     contextPath context -/- "build" -/- replaceEq '.' '/' moduleName <.> "hs"
 
 contextFiles :: Context -> Action [(String, Maybe FilePath)]
-contextFiles context @ Context {..} = do
+contextFiles context at Context {..} = do
     let path = contextPath context
     modules <- fmap sort . pkgDataList $ Modules path
     zip modules <$> askOracle (ModuleFilesKey context)
@@ -97,8 +103,8 @@ moduleFilesOracle = void $ do
 
     gens <- newCache $ \context -> do
         files <- contextFiles context
-        return $ Map.fromList [ (generatedFile context modName, (src, builder))
+        return $ Map.fromList [ (generatedFile context modName, src)
                               | (modName, Just src) <- files
-                              , let Just builder = determineBuilder src ]
+                              , takeExtension src `notElem` [".hs", ".lhs"] ]
 
     addOracle $ \(Generator (context, file)) -> Map.lookup file <$> gens context



More information about the ghc-commits mailing list