Let Cabal determine the package-db stack
This commit is contained in:
@@ -3,6 +3,7 @@ module Language.Haskell.GhcMod.World where
|
||||
import Language.Haskell.GhcMod.GhcPkg
|
||||
import Language.Haskell.GhcMod.PathsAndFiles
|
||||
import Language.Haskell.GhcMod.Types
|
||||
import Language.Haskell.GhcMod.Monad.Types
|
||||
import Language.Haskell.GhcMod.Utils
|
||||
|
||||
import Control.Applicative
|
||||
@@ -20,18 +21,19 @@ data World = World {
|
||||
, worldSymbolCache :: Maybe TimedFile
|
||||
} deriving (Eq, Show)
|
||||
|
||||
timedPackageCaches :: Cradle -> IO [TimedFile]
|
||||
timedPackageCaches crdl = do
|
||||
fs <- mapM mightExist . map (</> packageCache)
|
||||
=<< getPackageCachePaths libdir crdl
|
||||
timeFile `mapM` catMaybes fs
|
||||
timedPackageCaches :: IOish m => GhcModT m [TimedFile]
|
||||
timedPackageCaches = do
|
||||
fs <- mapM (liftIO . mightExist) . map (</> packageCache)
|
||||
=<< getPackageCachePaths libdir
|
||||
(liftIO . timeFile) `mapM` catMaybes fs
|
||||
|
||||
getCurrentWorld :: Cradle -> IO World
|
||||
getCurrentWorld crdl = do
|
||||
pkgCaches <- timedPackageCaches crdl
|
||||
mCabalFile <- timeFile `traverse` cradleCabalFile crdl
|
||||
mCabalConfig <- timeMaybe (setupConfigFile crdl)
|
||||
mSymbolCache <- timeMaybe (symbolCache crdl)
|
||||
getCurrentWorld :: IOish m => GhcModT m World
|
||||
getCurrentWorld = do
|
||||
crdl <- cradle
|
||||
pkgCaches <- timedPackageCaches
|
||||
mCabalFile <- liftIO $ timeFile `traverse` cradleCabalFile crdl
|
||||
mCabalConfig <- liftIO $ timeMaybe (setupConfigFile crdl)
|
||||
mSymbolCache <- liftIO $ timeMaybe (symbolCache crdl)
|
||||
|
||||
return World {
|
||||
worldPackageCaches = pkgCaches
|
||||
@@ -40,26 +42,9 @@ getCurrentWorld crdl = do
|
||||
, worldSymbolCache = mSymbolCache
|
||||
}
|
||||
|
||||
didWorldChange :: World -> Cradle -> IO Bool
|
||||
didWorldChange world crdl = do
|
||||
(world /=) <$> getCurrentWorld crdl
|
||||
|
||||
-- * Neither file exists -> should return False:
|
||||
-- @Nothing < Nothing = False@
|
||||
-- (since we don't need to @cabal configure@ when no cabal file exists.)
|
||||
--
|
||||
-- * Cabal file doesn't exist (unlikely case) -> should return False
|
||||
-- @Just cc < Nothing = False@
|
||||
-- TODO: should we delete dist/setup-config?
|
||||
--
|
||||
-- * dist/setup-config doesn't exist yet -> should return True:
|
||||
-- @Nothing < Just cf = True@
|
||||
--
|
||||
-- * Both files exist
|
||||
-- @Just cc < Just cf = cc < cf = cc `olderThan` cf@
|
||||
isSetupConfigOutOfDate :: World -> Bool
|
||||
isSetupConfigOutOfDate World {..} = do
|
||||
worldCabalConfig < worldCabalFile
|
||||
didWorldChange :: IOish m => World -> GhcModT m Bool
|
||||
didWorldChange world = do
|
||||
(world /=) <$> getCurrentWorld
|
||||
|
||||
isYoungerThanSetupConfig :: FilePath -> World -> IO Bool
|
||||
isYoungerThanSetupConfig file World {..} = do
|
||||
|
||||
Reference in New Issue
Block a user