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

242 lines
9.1 KiB
Haskell
Raw Normal View History

-- ghc-mod: Making Haskell development *more* fun
-- Copyright (C) 2015 Daniel Gröber <dxld ÄT darkboxed DOT org>
--
-- This program is free software: you can redistribute it and/or modify
-- it under the terms of the GNU Affero General Public License as published by
-- the Free Software Foundation, either version 3 of the License, or
-- (at your option) any later version.
--
-- This program is distributed in the hope that it will be useful,
-- but WITHOUT ANY WARRANTY; without even the implied warranty of
-- MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
-- GNU Affero General Public License for more details.
--
-- You should have received a copy of the GNU Affero General Public License
-- along with this program. If not, see <http://www.gnu.org/licenses/>.
2015-03-28 01:33:42 +00:00
{-# LANGUAGE CPP #-}
module Language.Haskell.GhcMod.CabalHelper
#ifndef SPEC
( getComponents
, getGhcMergedPkgOptions
, getCabalPackageDbStack
2015-08-17 05:41:46 +00:00
, getStackPackageDbStack
, getCustomPkgDbStack
, prepareCabalHelper
)
#endif
where
import Control.Applicative
import Control.Monad
import Control.Category ((.))
import Data.Maybe
import Data.Monoid
2015-06-07 01:36:50 +00:00
import Data.Serialize (Serialize)
import Data.Traversable
2015-03-15 19:48:55 +00:00
import Distribution.Helper
import qualified Language.Haskell.GhcMod.Types as T
import Language.Haskell.GhcMod.Types hiding (ghcProgram, ghcPkgProgram,
cabalProgram)
import Language.Haskell.GhcMod.Monad.Types
import Language.Haskell.GhcMod.Utils
import Language.Haskell.GhcMod.PathsAndFiles
import Language.Haskell.GhcMod.Logging
2015-08-13 07:01:58 +00:00
import Language.Haskell.GhcMod.Output
import System.FilePath
2015-08-17 05:41:46 +00:00
import System.Directory (findExecutable)
import Prelude hiding ((.))
2015-03-28 01:33:42 +00:00
import Paths_ghc_mod as GhcMod
-- | Only package related GHC options, sufficient for things that don't need to
-- access home modules
getGhcMergedPkgOptions :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m)
=> m [GHCOption]
2015-08-18 09:41:14 +00:00
getGhcMergedPkgOptions = chCached $ \distDir -> Cached {
cacheLens = Just (lGmcMergedPkgOptions . lGmCaches),
2015-08-18 09:41:14 +00:00
cacheFile = distDir </> mergedPkgOptsCacheFile,
2015-08-10 07:07:41 +00:00
cachedAction = \ _tcf (progs, rootdir, distdir, _) _ma -> do
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
opts <- withCabal $ runQuery'' readProc progs rootdir distdir $
ghcMergedPkgOptions
2015-08-18 09:41:14 +00:00
return ([distDir </> setupConfigPath], opts)
}
getCabalPackageDbStack :: (IOish m, GmEnv m, GmState m, GmLog m) => m [GhcPkgDb]
2015-08-18 09:41:14 +00:00
getCabalPackageDbStack = chCached $ \distDir -> Cached {
cacheLens = Just (lGmcPackageDbStack . lGmCaches),
2015-08-18 09:41:14 +00:00
cacheFile = distDir </> pkgDbStackCacheFile,
2015-08-10 07:07:41 +00:00
cachedAction = \ _tcf (progs, rootdir, distdir, _) _ma -> do
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
dbs <- withCabal $ map chPkgToGhcPkg <$> runQuery'' readProc progs rootdir distdir packageDbStack
2015-08-18 09:41:14 +00:00
return ([distDir </> setupConfigPath, sandboxConfigFile], dbs)
}
chPkgToGhcPkg :: ChPkgDb -> GhcPkgDb
chPkgToGhcPkg ChPkgGlobal = GlobalDb
chPkgToGhcPkg ChPkgUser = UserDb
chPkgToGhcPkg (ChPkgSpecific f) = PackageDb f
-- | Primary interface to cabal-helper and intended single entrypoint to
-- constructing 'GmComponent's
--
-- The Component\'s 'gmcHomeModuleGraph' will be empty and has to be resolved by
-- 'resolveGmComponents'.
getComponents :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m)
2015-08-03 01:09:56 +00:00
=> m [GmComponent 'GMCRaw ChEntrypoint]
2015-08-18 09:41:14 +00:00
getComponents = chCached$ \distDir -> Cached {
cacheLens = Just (lGmcComponents . lGmCaches),
2015-08-18 09:41:14 +00:00
cacheFile = distDir </> cabalHelperCacheFile,
2015-08-13 07:01:58 +00:00
cachedAction = \ _tcf (progs, rootdir, distdir, _vers) _ma -> do
readProc <- gmReadProcess
runQuery'' readProc progs rootdir distdir $ do
q <- join7
<$> ghcOptions
<*> ghcPkgOptions
<*> ghcSrcOptions
<*> ghcLangOptions
<*> entrypoints
<*> entrypoints
<*> sourceDirs
2015-05-05 12:44:42 +00:00
let cs = flip map q $ curry8 (GmComponent mempty)
2015-08-18 09:41:14 +00:00
return ([distDir </> setupConfigPath], cs)
}
2015-03-15 19:48:55 +00:00
where
2015-05-05 12:44:42 +00:00
curry8 fn (a, (b, (c, (d, (e, (f, (g, h))))))) = fn a b c d e f g h
join7 a b c d e f = join' a . join' b . join' c . join' d . join' e . join' f
2015-03-15 19:48:55 +00:00
join' :: Eq a => [(a,b)] -> [(a,c)] -> [(a,(b,c))]
join' lb lc = [ (a, (b, c))
| (a, b) <- lb
2015-05-05 12:44:42 +00:00
, (a', c) <- lc
, a == a'
]
2015-03-28 01:33:42 +00:00
prepareCabalHelper :: (IOish m, GmEnv m, GmLog m) => m ()
prepareCabalHelper = do
crdl <- cradle
let projdir = cradleRootDir crdl
2015-08-18 09:41:14 +00:00
distdir = projdir </> cradleDistDir crdl
readProc <- gmReadProcess
2015-08-18 12:55:45 +00:00
when (cradleProjectType crdl == CabalProject || cradleProjectType crdl == StackProject) $
withCabal $ liftIO $ prepare readProc projdir distdir
parseCustomPackageDb :: String -> [GhcPkgDb]
parseCustomPackageDb src = map parsePkgDb $ filter (not . null) $ lines src
where
parsePkgDb "global" = GlobalDb
parsePkgDb "user" = UserDb
parsePkgDb s = PackageDb s
getCustomPkgDbStack :: (IOish m, GmEnv m) => m (Maybe [GhcPkgDb])
getCustomPkgDbStack = do
mCusPkgDbFile <- liftIO . (traverse readFile <=< findCustomPackageDbFile) . cradleRootDir =<< cradle
return $ parseCustomPackageDb <$> mCusPkgDbFile
2015-08-17 05:41:46 +00:00
getStackPackageDbStack :: IOish m => m [GhcPkgDb]
getStackPackageDbStack = do
mstack <- liftIO $ findExecutable "stack"
case mstack of
Nothing -> return []
Just stack -> do
snapshotDb <- liftIO $ readProcess stack ["path", "--snapshot-pkg-db"] ""
localDb <- liftIO $ readProcess stack ["path", "--local-pkg-db"] ""
return $ map (PackageDb . takeWhile (/='\n')) [snapshotDb, localDb]
withCabal :: (IOish m, GmEnv m, GmLog m) => m a -> m a
withCabal action = do
crdl <- cradle
opts <- options
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
2015-08-12 07:04:09 +00:00
let projdir = cradleRootDir crdl
2015-08-18 09:41:14 +00:00
distdir = projdir </> cradleDistDir crdl
2015-08-12 07:04:09 +00:00
mCabalFile <- liftIO $ timeFile `traverse` cradleCabalFile crdl
mCabalConfig <- liftIO $ timeMaybe (setupConfigFile crdl)
mCusPkgDbStack <- getCustomPkgDbStack
pkgDbStackOutOfSync <-
case mCusPkgDbStack of
Just cusPkgDbStack -> do
2015-08-13 07:01:58 +00:00
pkgDb <- runQuery'' readProc (helperProgs opts) projdir distdir $
map chPkgToGhcPkg <$> packageDbStack
return $ pkgDb /= cusPkgDbStack
Nothing -> return False
cusPkgStack <- maybe [] ((PackageDb "clear"):) <$> getCustomPkgDbStack
--TODO: also invalidate when sandboxConfig file changed
when (isSetupConfigOutOfDate mCabalFile mCabalConfig) $
gmLog GmDebug "" $ strDoc $ "setup configuration is out of date, reconfiguring Cabal project."
when pkgDbStackOutOfSync $
gmLog GmDebug "" $ strDoc $ "package-db stack out of sync with ghc-mod.package-db-stack, reconfiguring Cabal project."
when (isSetupConfigOutOfDate mCabalFile mCabalConfig || pkgDbStackOutOfSync) $
withDirectory_ (cradleRootDir crdl) $ do
let progOpts =
2015-03-15 19:48:55 +00:00
[ "--with-ghc=" ++ T.ghcProgram opts ]
-- Only pass ghc-pkg if it was actually set otherwise we
-- might break cabal's guessing logic
2015-03-15 19:48:55 +00:00
++ if T.ghcPkgProgram opts /= T.ghcPkgProgram defaultOptions
then [ "--with-ghc-pkg=" ++ T.ghcPkgProgram opts ]
else []
++ map pkgDbArg cusPkgStack
2015-08-13 07:01:58 +00:00
liftIO $ void $ readProc (T.cabalProgram opts) ("configure":progOpts) ""
gmLog GmDebug "" $ strDoc $ "writing Cabal autogen files"
2015-08-13 07:01:58 +00:00
liftIO $ writeAutogenFiles readProc projdir distdir
action
2015-03-03 11:18:54 +00:00
pkgDbArg :: GhcPkgDb -> String
pkgDbArg GlobalDb = "--package-db=global"
pkgDbArg UserDb = "--package-db=user"
pkgDbArg (PackageDb p) = "--package-db=" ++ p
-- * 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 :: Maybe TimedFile -> Maybe TimedFile -> Bool
isSetupConfigOutOfDate worldCabalFile worldCabalConfig = do
worldCabalConfig < worldCabalFile
helperProgs :: Options -> Programs
helperProgs opts = Programs {
cabalProgram = T.cabalProgram opts,
ghcProgram = T.ghcProgram opts,
ghcPkgProgram = T.ghcPkgProgram opts
}
chCached :: (Applicative m, IOish m, GmEnv m, GmState m, GmLog m, Serialize a)
2015-08-18 09:41:14 +00:00
=> (FilePath -> Cached m GhcModState ChCacheData a) -> m a
chCached c = do
root <- cradleRootDir <$> cradle
2015-08-18 09:41:14 +00:00
dist <- cradleDistDir <$> cradle
d <- cacheInputData root dist
withCabal $ cached root (c dist) d
where
2015-08-18 09:41:14 +00:00
cacheInputData root dist = do
opt <- options
return $ ( helperProgs opt
2015-08-10 07:07:41 +00:00
, root
2015-08-18 09:41:14 +00:00
, root </> dist
, (gmVer, chVer)
)
gmVer = GhcMod.version
chVer = VERSION_cabal_helper