Fix all the stack related things

This commit is contained in:
Daniel Gröber
2015-08-19 06:48:27 +02:00
parent d660e7cd85
commit 78bdf86a95
11 changed files with 75 additions and 59 deletions

View File

@@ -53,24 +53,24 @@ import Paths_ghc_mod as GhcMod
-- access home modules
getGhcMergedPkgOptions :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m)
=> m [GHCOption]
getGhcMergedPkgOptions = chCached $ \distDir -> Cached {
getGhcMergedPkgOptions = chCached $ \distdir -> Cached {
cacheLens = Just (lGmcMergedPkgOptions . lGmCaches),
cacheFile = distDir </> mergedPkgOptsCacheFile,
cachedAction = \ _tcf (progs, rootdir, distdir, _) _ma -> do
cacheFile = mergedPkgOptsCacheFile distdir,
cachedAction = \ _tcf (progs, rootdir, _) _ma -> do
readProc <- gmReadProcess
opts <- withCabal $ runQuery'' readProc progs rootdir distdir $
ghcMergedPkgOptions
return ([distDir </> setupConfigPath], opts)
return ([setupConfigPath distdir], opts)
}
getCabalPackageDbStack :: (IOish m, GmEnv m, GmState m, GmLog m) => m [GhcPkgDb]
getCabalPackageDbStack = chCached $ \distDir -> Cached {
getCabalPackageDbStack = chCached $ \distdir -> Cached {
cacheLens = Just (lGmcPackageDbStack . lGmCaches),
cacheFile = distDir </> pkgDbStackCacheFile,
cachedAction = \ _tcf (progs, rootdir, distdir, _) _ma -> do
cacheFile = pkgDbStackCacheFile distdir,
cachedAction = \ _tcf (progs, rootdir, _) _ma -> do
readProc <- gmReadProcess
dbs <- withCabal $ map chPkgToGhcPkg <$> runQuery'' readProc progs rootdir distdir packageDbStack
return ([distDir </> setupConfigPath, sandboxConfigFile], dbs)
return ([setupConfigPath distdir, sandboxConfigFile], dbs)
}
chPkgToGhcPkg :: ChPkgDb -> GhcPkgDb
@@ -85,10 +85,10 @@ chPkgToGhcPkg (ChPkgSpecific f) = PackageDb f
-- 'resolveGmComponents'.
getComponents :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m)
=> m [GmComponent 'GMCRaw ChEntrypoint]
getComponents = chCached$ \distDir -> Cached {
getComponents = chCached$ \distdir -> Cached {
cacheLens = Just (lGmcComponents . lGmCaches),
cacheFile = distDir </> cabalHelperCacheFile,
cachedAction = \ _tcf (progs, rootdir, distdir, _vers) _ma -> do
cacheFile = cabalHelperCacheFile distdir,
cachedAction = \ _tcf (progs, rootdir, _vers) _ma -> do
readProc <- gmReadProcess
runQuery'' readProc progs rootdir distdir $ do
q <- join7
@@ -100,7 +100,7 @@ getComponents = chCached$ \distDir -> Cached {
<*> entrypoints
<*> sourceDirs
let cs = flip map q $ curry8 (GmComponent mempty)
return ([distDir </> setupConfigPath], cs)
return ([setupConfigPath distdir], cs)
}
where
curry8 fn (a, (b, (c, (d, (e, (f, (g, h))))))) = fn a b c d e f g h
@@ -226,14 +226,15 @@ chCached :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m, Serialize a)
chCached c = do
root <- cradleRootDir <$> cradle
dist <- cradleDistDir <$> cradle
d <- cacheInputData root dist
d <- cacheInputData root
withCabal $ cached root (c dist) d
where
cacheInputData root dist = do
-- we don't need to include the disdir in the cache input because when it
-- changes the cache files will be gone anyways ;)
cacheInputData root = do
opt <- options
return $ ( helperProgs opt
, root
, root </> dist
, (gmVer, chVer)
)

View File

@@ -49,4 +49,4 @@ data TimedCacheFiles = TimedCacheFiles {
-- ^ Timestamped files returned by the cached action
} deriving (Eq, Ord, Show)
type ChCacheData = (Programs, FilePath, FilePath, (Version, [Char]))
type ChCacheData = (Programs, FilePath, (Version, [Char]))

View File

@@ -75,7 +75,7 @@ stackCradle wdir = do
let cabalDir = takeDirectory cabalFile
_stackConfigFile <- MaybeT $ findStackConfigFile cabalDir
distDir <- liftIO $ findStackDistDir cabalDir
distDir <- MaybeT $ getStackDistDir cabalDir
return Cradle {
cradleProjectType = StackProject

View File

@@ -22,6 +22,7 @@ module Language.Haskell.GhcMod.PathsAndFiles (
import Config (cProjectVersion)
import Control.Applicative
import Control.Monad
import Control.Monad.Trans.Maybe
import Data.List
import Data.Char
import Data.Maybe
@@ -74,13 +75,10 @@ findCabalFile dir = do
findStackConfigFile :: FilePath -> IO (Maybe FilePath)
findStackConfigFile dir = mightExist (dir </> "stack.yaml")
findStackDistDir :: FilePath -> IO FilePath
findStackDistDir dir = U.withDirectory_ dir $ do
mstack <- liftIO $ findExecutable "stack"
case mstack of
Nothing -> return "dist"
Just stack ->
takeWhile (/='\n') <$> readProcess stack ["path", "--dist-dir"] ""
getStackDistDir :: FilePath -> IO (Maybe FilePath)
getStackDistDir dir = U.withDirectory_ dir $ runMaybeT $ do
stack <- MaybeT $ findExecutable "stack"
liftIO $ takeWhile (/='\n') <$> readProcess stack ["path", "--dist-dir"] ""
-- | Get path to sandbox config file
getSandboxDb :: FilePath
@@ -190,14 +188,16 @@ parents dir' =
----------------------------------------------------------------
setupConfigFile :: Cradle -> FilePath
setupConfigFile crdl = cradleRootDir crdl </> cradleDistDir crdl </> setupConfigPath
setupConfigFile crdl =
cradleRootDir crdl </> setupConfigPath (cradleDistDir crdl)
sandboxConfigFile :: FilePath
sandboxConfigFile = "cabal.sandbox.config"
-- | Path to 'LocalBuildInfo' file, usually @dist/setup-config@
setupConfigPath :: FilePath
setupConfigPath = "setup-config" -- localBuildInfoFile defaultDistPref
setupConfigPath :: FilePath -> FilePath
setupConfigPath dist = dist </> "setup-config"
-- localBuildInfoFile defaultDistPref
macrosHeaderPath :: FilePath
macrosHeaderPath = "build/autogen/cabal_macros.h"
@@ -216,17 +216,21 @@ symbolCache crdl = cradleTempDir crdl </> symbolCacheFile
symbolCacheFile :: String
symbolCacheFile = "ghc-mod.symbol-cache"
resolvedComponentsCacheFile :: String
resolvedComponentsCacheFile = setupConfigPath <.> "ghc-mod.resolved-components"
resolvedComponentsCacheFile :: FilePath -> FilePath
resolvedComponentsCacheFile dist =
setupConfigPath dist <.> "ghc-mod.resolved-components"
cabalHelperCacheFile :: String
cabalHelperCacheFile = setupConfigPath <.> "ghc-mod.cabal-components"
cabalHelperCacheFile :: FilePath -> FilePath
cabalHelperCacheFile dist =
setupConfigPath dist <.> "ghc-mod.cabal-components"
mergedPkgOptsCacheFile :: String
mergedPkgOptsCacheFile = setupConfigPath <.> "ghc-mod.package-options"
mergedPkgOptsCacheFile :: FilePath -> FilePath
mergedPkgOptsCacheFile dist =
setupConfigPath dist <.> "ghc-mod.package-options"
pkgDbStackCacheFile :: String
pkgDbStackCacheFile = setupConfigPath <.> "ghc-mod.package-db-stack"
pkgDbStackCacheFile :: FilePath -> FilePath
pkgDbStackCacheFile dist =
setupConfigPath dist <.> "ghc-mod.package-db-stack"
-- | @findCustomPackageDbFile 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

@@ -182,9 +182,9 @@ resolvedComponentsCache :: IOish m => FilePath ->
Cached (GhcModT m) GhcModState
[GmComponent 'GMCRaw (Set.Set ModulePath)]
(Map.Map ChComponentName (GmComponent 'GMCResolved (Set.Set ModulePath)))
resolvedComponentsCache distDir = Cached {
resolvedComponentsCache distdir = Cached {
cacheLens = Just (lGmcResolvedComponents . lGmCaches),
cacheFile = distDir </> resolvedComponentsCacheFile,
cacheFile = resolvedComponentsCacheFile distdir,
cachedAction = \tcfs comps ma -> do
Cradle {..} <- cradle
let iifsM = invalidatingInputFiles tcfs
@@ -195,13 +195,13 @@ resolvedComponentsCache distDir = Cached {
Just iifs ->
let
filterOutSetupCfg =
filter (/= cradleRootDir </> cradleDistDir </> setupConfigPath)
filter (/= cradleRootDir </> setupConfigPath distdir)
changedFiles = filterOutSetupCfg iifs
in if null changedFiles
then Nothing
else Just $ map Left changedFiles
setupChanged = maybe False
(elem $ cradleRootDir </> cradleDistDir </> setupConfigPath)
(elem $ cradleRootDir </> setupConfigPath distdir)
iifsM
case (setupChanged, ma) of
(False, Just mcs) -> gmsGet >>= \s -> gmsPut s { gmComponents = mcs }
@@ -218,7 +218,7 @@ resolvedComponentsCache distDir = Cached {
text "files changed" <+>: changedDoc
mcs <- resolveGmComponents mums comps
return ((cradleDistDir </> setupConfigPath) : flatten mcs , mcs)
return (setupConfigPath distdir : flatten mcs , mcs)
}
where