Fix #487, Modules from sandbox not visible
This commit is contained in:
parent
1e381a12a9
commit
49515b3eb8
@ -17,7 +17,7 @@
|
|||||||
{-# LANGUAGE CPP #-}
|
{-# LANGUAGE CPP #-}
|
||||||
module Language.Haskell.GhcMod.CabalHelper (
|
module Language.Haskell.GhcMod.CabalHelper (
|
||||||
getComponents
|
getComponents
|
||||||
, getGhcPkgOptions
|
, getGhcMergedPkgOptions
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Applicative
|
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
|
-- | Only package related GHC options, sufficient for things that don't need to
|
||||||
-- access home modules
|
-- access home modules
|
||||||
getGhcPkgOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
|
getGhcMergedPkgOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
|
||||||
=> m [(ChComponentName, [GHCOption])]
|
=> m [GHCOption]
|
||||||
getGhcPkgOptions = map (\c -> (gmcName c, gmcGhcPkgOpts c)) `liftM` getComponents
|
getGhcMergedPkgOptions = chCached Cached {
|
||||||
|
cacheFile = mergedPkgOptsCacheFile,
|
||||||
|
cachedAction = \ _ (progs, root, _) _ -> do
|
||||||
|
opts <- withCabal $ runQuery' progs root $ ghcMergedPkgOptions
|
||||||
|
return ([setupConfigPath], opts)
|
||||||
|
}
|
||||||
|
|
||||||
helperProgs :: Options -> Programs
|
helperProgs :: Options -> Programs
|
||||||
helperProgs opts = Programs {
|
helperProgs opts = Programs {
|
||||||
@ -56,16 +61,22 @@ helperProgs opts = Programs {
|
|||||||
-- 'resolveGmComponents'.
|
-- 'resolveGmComponents'.
|
||||||
getComponents :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
|
getComponents :: (Applicative m, MonadIO m, GmEnv m, GmLog m)
|
||||||
=> m [GmComponent GMCRaw ChEntrypoint]
|
=> m [GmComponent GMCRaw ChEntrypoint]
|
||||||
getComponents = do
|
getComponents = chCached cabalHelperCache
|
||||||
|
|
||||||
|
chCached c = do
|
||||||
|
root <- cradleRootDir <$> cradle
|
||||||
|
d <- cacheInputData root
|
||||||
|
withCabal $ cached root c d
|
||||||
|
where
|
||||||
|
cacheInputData root = do
|
||||||
opt <- options
|
opt <- options
|
||||||
Cradle {..} <- cradle
|
return $ ( helperProgs opt
|
||||||
let gmVer = GhcMod.version
|
, root </> "dist"
|
||||||
chVer = VERSION_cabal_helper
|
|
||||||
d = (helperProgs opt
|
|
||||||
, cradleRootDir </> "dist"
|
|
||||||
, (gmVer, chVer)
|
, (gmVer, chVer)
|
||||||
)
|
)
|
||||||
withCabal $ cached cradleRootDir cabalHelperCache d
|
|
||||||
|
gmVer = GhcMod.version
|
||||||
|
chVer = VERSION_cabal_helper
|
||||||
|
|
||||||
cabalHelperCache
|
cabalHelperCache
|
||||||
:: (Functor m, Applicative m, MonadIO m)
|
:: (Functor m, Applicative m, MonadIO m)
|
||||||
|
@ -30,11 +30,16 @@ debugInfo = do
|
|||||||
Just _ -> cabalDebug
|
Just _ -> cabalDebug
|
||||||
Nothing -> return []
|
Nothing -> return []
|
||||||
|
|
||||||
|
pkgOpts <- packageGhcOptions
|
||||||
|
|
||||||
return $ unlines $
|
return $ unlines $
|
||||||
[ "Root directory: " ++ cradleRootDir
|
[ "Root directory: " ++ cradleRootDir
|
||||||
, "Current directory: " ++ cradleCurrentDir
|
, "Current directory: " ++ cradleCurrentDir
|
||||||
|
, "GHC Package flags:\n" ++ render (nest 4 $
|
||||||
|
fsep $ map text pkgOpts)
|
||||||
, "GHC System libraries: " ++ ghcLibDir
|
, "GHC System libraries: " ++ ghcLibDir
|
||||||
, "GHC user options: " ++ render (fsep $ map text ghcUserOptions)
|
, "GHC user options:\n" ++ render (nest 4 $
|
||||||
|
fsep $ map text ghcUserOptions)
|
||||||
] ++ cabal
|
] ++ cabal
|
||||||
|
|
||||||
cabalDebug :: IOish m => GhcModT m [String]
|
cabalDebug :: IOish m => GhcModT m [String]
|
||||||
|
@ -205,7 +205,10 @@ resolvedComponentsCacheFile :: String
|
|||||||
resolvedComponentsCacheFile = setupConfigPath <.> "ghc-mod.resolved-components"
|
resolvedComponentsCacheFile = setupConfigPath <.> "ghc-mod.resolved-components"
|
||||||
|
|
||||||
cabalHelperCacheFile :: String
|
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@.
|
-- | @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@
|
-- If it exists in the given directory it is returned otherwise @findCradleFile@ returns @Nothing@
|
||||||
|
@ -73,8 +73,8 @@ withLightHscEnv opts action = gbracket initEnv teardownEnv action
|
|||||||
dflags' <- runLightGhc env $ do
|
dflags' <- runLightGhc env $ do
|
||||||
-- HomeModuleGraph and probably all other clients get into all sorts of
|
-- HomeModuleGraph and probably all other clients get into all sorts of
|
||||||
-- trouble if the package state isn't initialized here
|
-- trouble if the package state isn't initialized here
|
||||||
_ <- setSessionDynFlags =<< getSessionDynFlags
|
_ <- setSessionDynFlags =<< addCmdOpts opts =<< getSessionDynFlags
|
||||||
addCmdOpts opts =<< getSessionDynFlags
|
getSessionDynFlags
|
||||||
newHscEnv dflags'
|
newHscEnv dflags'
|
||||||
|
|
||||||
runLightGhc :: HscEnv -> LightGhc a -> IO a
|
runLightGhc :: HscEnv -> LightGhc a -> IO a
|
||||||
@ -263,8 +263,7 @@ packageGhcOptions :: (Applicative m, MonadIO m, GmEnv m, GmLog m) => m [GHCOptio
|
|||||||
packageGhcOptions = do
|
packageGhcOptions = do
|
||||||
crdl <- cradle
|
crdl <- cradle
|
||||||
case cradleCabalFile crdl of
|
case cradleCabalFile crdl of
|
||||||
Just _ ->
|
Just _ -> getGhcMergedPkgOptions
|
||||||
(Set.toList . Set.fromList . concat . map snd) `liftM` getGhcPkgOptions
|
|
||||||
Nothing -> sandboxOpts crdl
|
Nothing -> sandboxOpts crdl
|
||||||
|
|
||||||
sandboxOpts :: Monad m => Cradle -> m [String]
|
sandboxOpts :: Monad m => Cradle -> m [String]
|
||||||
|
@ -121,7 +121,7 @@ Library
|
|||||||
, bytestring
|
, bytestring
|
||||||
, cereal >= 0.4
|
, cereal >= 0.4
|
||||||
, containers
|
, containers
|
||||||
, cabal-helper >= 0.3.3.0
|
, cabal-helper >= 0.3.5.0
|
||||||
, deepseq
|
, deepseq
|
||||||
, directory
|
, directory
|
||||||
, filepath
|
, filepath
|
||||||
|
Loading…
Reference in New Issue
Block a user