ghc-mod/Language/Haskell/GhcMod/World.hs

68 lines
2.1 KiB
Haskell
Raw Normal View History

2014-11-01 21:02:47 +00:00
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.Utils
2015-08-03 01:09:56 +00:00
import Control.Applicative
2014-11-01 21:02:47 +00:00
import Data.Maybe
2015-08-03 01:09:56 +00:00
import Data.Traversable
2014-11-01 21:02:47 +00:00
import System.FilePath ((</>))
import GHC.Paths (libdir)
2015-08-03 01:09:56 +00:00
import Prelude
2014-11-01 21:02:47 +00:00
data World = World {
worldPackageCaches :: [TimedFile]
, worldCabalFile :: Maybe TimedFile
, worldCabalConfig :: Maybe TimedFile
, worldSymbolCache :: Maybe TimedFile
2014-11-01 21:02:47 +00:00
} deriving (Eq, Show)
timedPackageCaches :: Cradle -> IO [TimedFile]
timedPackageCaches crdl = do
2014-11-01 21:02:47 +00:00
fs <- mapM mightExist . map (</> packageCache)
=<< getPackageCachePaths libdir crdl
timeFile `mapM` catMaybes fs
getCurrentWorld :: Cradle -> IO World
getCurrentWorld crdl = do
pkgCaches <- timedPackageCaches crdl
2014-11-01 21:02:47 +00:00
mCabalFile <- timeFile `traverse` cradleCabalFile crdl
mCabalConfig <- timeMaybe (setupConfigFile crdl)
mSymbolCache <- timeMaybe (symbolCache crdl)
2014-11-01 21:02:47 +00:00
return World {
worldPackageCaches = pkgCaches
, worldCabalFile = mCabalFile
, worldCabalConfig = mCabalConfig
, worldSymbolCache = mSymbolCache
2014-11-01 21:02:47 +00:00
}
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
isYoungerThanSetupConfig :: FilePath -> World -> IO Bool
isYoungerThanSetupConfig file World {..} = do
tfile <- timeFile file
return $ worldCabalConfig < Just tfile