Fix #487, Modules from sandbox not visible

This commit is contained in:
Daniel Gröber 2015-06-05 22:42:46 +02:00
parent 1e381a12a9
commit 49515b3eb8
5 changed files with 39 additions and 21 deletions

View File

@ -17,7 +17,7 @@
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.CabalHelper (
getComponents
, getGhcPkgOptions
, getGhcMergedPkgOptions
) where
import Control.Applicative
@ -38,9 +38,14 @@ import Paths_ghc_mod as GhcMod
-- | Only package related GHC options, sufficient for things that don't need to
-- access home modules
getGhcPkgOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
=> m [(ChComponentName, [GHCOption])]
getGhcPkgOptions = map (\c -> (gmcName c, gmcGhcPkgOpts c)) `liftM` getComponents
getGhcMergedPkgOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
=> m [GHCOption]
getGhcMergedPkgOptions = chCached Cached {
cacheFile = mergedPkgOptsCacheFile,
cachedAction = \ _ (progs, root, _) _ -> do
opts <- withCabal $ runQuery' progs root $ ghcMergedPkgOptions
return ([setupConfigPath], opts)
}
helperProgs :: Options -> Programs
helperProgs opts = Programs {
@ -56,16 +61,22 @@ helperProgs opts = Programs {
-- 'resolveGmComponents'.
getComponents :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
=> m [GmComponent GMCRaw ChEntrypoint]
getComponents = do
opt <- options
Cradle {..} <- cradle
let gmVer = GhcMod.version
chVer = VERSION_cabal_helper
d = (helperProgs opt
, cradleRootDir </> "dist"
, (gmVer, chVer)
)
withCabal $ cached cradleRootDir cabalHelperCache d
getComponents = chCached cabalHelperCache
chCached c = do
root <- cradleRootDir <$> cradle
d <- cacheInputData root
withCabal $ cached root c d
where
cacheInputData root = do
opt <- options
return $ ( helperProgs opt
, root </> "dist"
, (gmVer, chVer)
)
gmVer = GhcMod.version
chVer = VERSION_cabal_helper
cabalHelperCache
:: (Functor m, Applicative m, MonadIO m)

View File

@ -30,11 +30,16 @@ debugInfo = do
Just _ -> cabalDebug
Nothing -> return []
pkgOpts <- packageGhcOptions
return $ unlines $
[ "Root directory: " ++ cradleRootDir
, "Current directory: " ++ cradleCurrentDir
, "GHC Package flags:\n" ++ render (nest 4 $
fsep $ map text pkgOpts)
, "GHC System libraries: " ++ ghcLibDir
, "GHC user options: " ++ render (fsep $ map text ghcUserOptions)
, "GHC user options:\n" ++ render (nest 4 $
fsep $ map text ghcUserOptions)
] ++ cabal
cabalDebug :: IOish m => GhcModT m [String]

View File

@ -205,7 +205,10 @@ resolvedComponentsCacheFile :: String
resolvedComponentsCacheFile = setupConfigPath <.> "ghc-mod.resolved-components"
cabalHelperCacheFile :: String
cabalHelperCacheFile = setupConfigPath <.> "ghc-mod.cabal-helper"
cabalHelperCacheFile = setupConfigPath <.> "ghc-mod.cabal-components"
mergedPkgOptsCacheFile :: String
mergedPkgOptsCacheFile = setupConfigPath <.> "ghc-mod.package-options"
-- | @findCradleFile dir@. Searches for a @.ghc-mod.cradle@ file in @dir@.
-- If it exists in the given directory it is returned otherwise @findCradleFile@ returns @Nothing@

View File

@ -73,8 +73,8 @@ withLightHscEnv opts action = gbracket initEnv teardownEnv action
dflags' <- runLightGhc env $ do
-- HomeModuleGraph and probably all other clients get into all sorts of
-- trouble if the package state isn't initialized here
_ <- setSessionDynFlags =<< getSessionDynFlags
addCmdOpts opts =<< getSessionDynFlags
_ <- setSessionDynFlags =<< addCmdOpts opts =<< getSessionDynFlags
getSessionDynFlags
newHscEnv dflags'
runLightGhc :: HscEnv -> LightGhc a -> IO a
@ -263,8 +263,7 @@ packageGhcOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m) => m [GHCOptio
packageGhcOptions = do
crdl <- cradle
case cradleCabalFile crdl of
Just _ ->
(Set.toList . Set.fromList . concat . map snd) `liftM` getGhcPkgOptions
Just _ -> getGhcMergedPkgOptions
Nothing -> sandboxOpts crdl
sandboxOpts :: Monad m => Cradle -> m [String]

View File

@ -121,7 +121,7 @@ Library
, bytestring
, cereal >= 0.4
, containers
, cabal-helper >= 0.3.3.0
, cabal-helper >= 0.3.5.0
, deepseq
, directory
, filepath