2015-03-03 20:12:43 +00:00
-- 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 # -}
2015-08-07 04:47:34 +00:00
module Language.Haskell.GhcMod.CabalHelper
# ifndef SPEC
( getComponents
2015-06-05 20:42:46 +00:00
, getGhcMergedPkgOptions
2015-08-14 08:28:32 +00:00
, getCabalPackageDbStack
2015-08-17 05:41:46 +00:00
, getStackPackageDbStack
2015-08-14 08:28:32 +00:00
, getCustomPkgDbStack
2015-08-14 01:48:29 +00:00
, prepareCabalHelper
2015-08-07 04:47:34 +00:00
)
# endif
where
2015-03-03 20:12:43 +00:00
import Control.Applicative
import Control.Monad
2015-08-11 04:35:14 +00:00
import Control.Category ( ( . ) )
2015-08-07 04:47:34 +00:00
import Data.Maybe
2015-03-03 20:12:43 +00:00
import Data.Monoid
2015-06-07 01:36:50 +00:00
import Data.Serialize ( Serialize )
2015-08-07 04:47:34 +00:00
import Data.Traversable
2015-08-28 07:44:20 +00:00
import Distribution.Helper hiding ( Programs ( .. ) )
import qualified Distribution.Helper as CH
2015-03-15 19:48:55 +00:00
import qualified Language.Haskell.GhcMod.Types as T
2015-08-28 07:44:20 +00:00
import Language.Haskell.GhcMod.Types
2015-03-03 20:12:43 +00:00
import Language.Haskell.GhcMod.Monad.Types
import Language.Haskell.GhcMod.Utils
import Language.Haskell.GhcMod.PathsAndFiles
2015-08-03 03:20:14 +00:00
import Language.Haskell.GhcMod.Logging
2015-08-13 07:01:58 +00:00
import Language.Haskell.GhcMod.Output
2015-03-03 20:12:43 +00:00
import System.FilePath
2015-08-17 05:41:46 +00:00
import System.Directory ( findExecutable )
2015-08-28 07:44:20 +00:00
import System.Process
import System.Exit
2015-08-11 04:35:14 +00:00
import Prelude hiding ( ( . ) )
2015-03-03 20:12:43 +00:00
2015-03-28 01:33:42 +00:00
import Paths_ghc_mod as GhcMod
2015-03-03 20:12:43 +00:00
-- | Only package related GHC options, sufficient for things that don't need to
-- access home modules
2015-09-01 08:27:12 +00:00
getGhcMergedPkgOptions :: ( Applicative m , IOish m , Gm m )
2015-08-11 04:35:14 +00:00
=> m [ GHCOption ]
2015-08-19 04:48:27 +00:00
getGhcMergedPkgOptions = chCached $ \ distdir -> Cached {
2015-08-11 04:35:14 +00:00
cacheLens = Just ( lGmcMergedPkgOptions . lGmCaches ) ,
2015-08-19 04:48:27 +00:00
cacheFile = mergedPkgOptsCacheFile distdir ,
cachedAction = \ _tcf ( progs , rootdir , _ ) _ma -> do
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
opts <- withCabal $ runQuery'' readProc progs rootdir distdir $
ghcMergedPkgOptions
2015-08-19 04:48:27 +00:00
return ( [ setupConfigPath distdir ] , opts )
2015-06-05 20:42:46 +00:00
}
2015-03-03 20:12:43 +00:00
2015-09-01 08:27:12 +00:00
getCabalPackageDbStack :: ( IOish m , Gm m ) => m [ GhcPkgDb ]
2015-08-19 04:48:27 +00:00
getCabalPackageDbStack = chCached $ \ distdir -> Cached {
2015-08-11 04:35:14 +00:00
cacheLens = Just ( lGmcPackageDbStack . lGmCaches ) ,
2015-08-19 04:48:27 +00:00
cacheFile = pkgDbStackCacheFile distdir ,
cachedAction = \ _tcf ( progs , rootdir , _ ) _ma -> do
2015-08-19 06:46:56 +00:00
crdl <- cradle
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
dbs <- withCabal $ map chPkgToGhcPkg <$> runQuery'' readProc progs rootdir distdir packageDbStack
2015-08-19 06:46:56 +00:00
return ( [ setupConfigFile crdl , sandboxConfigFile crdl ] , dbs )
2015-08-07 04:47:34 +00:00
}
chPkgToGhcPkg :: ChPkgDb -> GhcPkgDb
chPkgToGhcPkg ChPkgGlobal = GlobalDb
chPkgToGhcPkg ChPkgUser = UserDb
chPkgToGhcPkg ( ChPkgSpecific f ) = PackageDb f
2015-03-03 20:12:43 +00:00
-- | 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'.
2015-09-01 08:27:12 +00:00
getComponents :: ( Applicative m , IOish m , Gm m )
2015-08-03 01:09:56 +00:00
=> m [ GmComponent 'GMCRaw ChEntrypoint ]
2015-08-19 04:48:27 +00:00
getComponents = chCached $ \ distdir -> Cached {
2015-08-11 04:35:14 +00:00
cacheLens = Just ( lGmcComponents . lGmCaches ) ,
2015-08-19 04:48:27 +00:00
cacheFile = cabalHelperCacheFile distdir ,
cachedAction = \ _tcf ( progs , rootdir , _vers ) _ma -> do
2015-08-13 07:01:58 +00:00
readProc <- gmReadProcess
runQuery'' readProc progs rootdir distdir $ do
2015-05-17 20:22:56 +00:00
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-19 04:48:27 +00:00
return ( [ setupConfigPath distdir ] , cs )
2015-03-28 01:30:51 +00:00
}
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 ) )
2015-05-17 20:22:56 +00:00
| ( a , b ) <- lb
2015-05-05 12:44:42 +00:00
, ( a' , c ) <- lc
, a == a'
]
2015-03-28 01:33:42 +00:00
2015-09-01 08:27:12 +00:00
prepareCabalHelper :: ( IOish m , GmEnv m , GmOut m , GmLog m ) => m ()
2015-08-14 01:48:29 +00:00
prepareCabalHelper = do
crdl <- cradle
let projdir = cradleRootDir crdl
2015-08-18 09:41:14 +00:00
distdir = projdir </> cradleDistDir crdl
2015-08-14 01:48:29 +00:00
readProc <- gmReadProcess
2015-08-18 12:55:45 +00:00
when ( cradleProjectType crdl == CabalProject || cradleProjectType crdl == StackProject ) $
2015-08-14 04:32:20 +00:00
withCabal $ liftIO $ prepare readProc projdir distdir
2015-08-14 01:48:29 +00:00
2015-08-14 08:28:32 +00:00
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 ]
2015-09-01 08:27:12 +00:00
patchStackPrograms :: ( IOish m , GmOut m ) => Cradle -> Programs -> m Programs
patchStackPrograms crdl progs
2015-08-28 07:44:20 +00:00
| cradleProjectType crdl /= StackProject = return progs
2015-09-01 08:27:12 +00:00
patchStackPrograms crdl progs = do
2015-08-28 07:44:20 +00:00
let projdir = cradleRootDir crdl
2015-09-01 08:27:12 +00:00
Just ghc <- getStackGhcPath projdir
Just ghcPkg <- getStackGhcPkgPath projdir
2015-08-28 07:44:20 +00:00
return $ progs {
ghcProgram = ghc
, ghcPkgProgram = ghcPkg
}
2015-09-01 08:27:12 +00:00
withCabal :: ( IOish m , GmEnv m , GmOut m , GmLog m ) => m a -> m a
2015-03-03 20:12:43 +00:00
withCabal action = do
crdl <- cradle
2015-03-07 18:23:55 +00:00
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
2015-08-19 06:46:56 +00:00
mCabalFile <- liftIO $ timeFile ` traverse ` cradleCabalFile crdl
mCabalConfig <- liftIO $ timeMaybe ( setupConfigFile crdl )
mCabalSandboxConfig <- liftIO $ timeMaybe ( sandboxConfigFile crdl )
2015-08-07 04:47:34 +00:00
mCusPkgDbStack <- getCustomPkgDbStack
pkgDbStackOutOfSync <-
case mCusPkgDbStack of
Just cusPkgDbStack -> do
2015-09-01 08:27:12 +00:00
pkgDb <- runQuery'' readProc ( helperProgs $ optPrograms opts ) projdir distdir $
2015-08-07 04:47:34 +00:00
map chPkgToGhcPkg <$> packageDbStack
return $ pkgDb /= cusPkgDbStack
Nothing -> return False
2015-08-19 07:04:25 +00:00
projType <- cradleProjectType <$> cradle
2015-08-11 04:35:14 +00:00
2015-08-07 04:47:34 +00:00
when ( isSetupConfigOutOfDate mCabalFile mCabalConfig ) $
gmLog GmDebug " " $ strDoc $ " setup configuration is out of date, reconfiguring Cabal project. "
2015-08-19 06:46:56 +00:00
when ( isSetupConfigOutOfDate mCabalSandboxConfig mCabalConfig ) $
gmLog GmDebug " " $ strDoc $ " sandbox configuration is out of date, reconfiguring Cabal project. "
2015-08-07 04:47:34 +00:00
when pkgDbStackOutOfSync $
gmLog GmDebug " " $ strDoc $ " package-db stack out of sync with ghc-mod.package-db-stack, reconfiguring Cabal project. "
2015-08-19 06:46:56 +00:00
when ( isSetupConfigOutOfDate mCabalFile mCabalConfig
|| pkgDbStackOutOfSync
|| isSetupConfigOutOfDate mCabalSandboxConfig mCabalConfig ) $
2015-08-19 07:04:25 +00:00
case projType of
CabalProject ->
2015-09-01 08:27:12 +00:00
cabalReconfigure readProc ( optPrograms opts ) crdl projdir distdir
2015-08-19 07:04:25 +00:00
StackProject ->
2015-08-28 07:44:20 +00:00
2015-09-01 08:27:12 +00:00
stackReconfigure crdl ( optPrograms opts )
2015-08-19 07:04:25 +00:00
_ ->
error $ " withCabal: unsupported project type: " ++ show projType
2015-03-03 20:12:43 +00:00
action
2015-03-03 11:18:54 +00:00
2015-08-19 07:04:25 +00:00
where
2015-09-02 02:57:25 +00:00
writeAutogen projdir distdir = do
readProc <- gmReadProcess
gmLog GmDebug " " $ strDoc $ " writing Cabal autogen files "
liftIO $ writeAutogenFiles readProc projdir distdir
2015-08-28 07:44:20 +00:00
cabalReconfigure readProc progs crdl projdir distdir = do
2015-08-19 07:04:25 +00:00
withDirectory_ ( cradleRootDir crdl ) $ do
cusPkgStack <- maybe [] ( ( PackageDb " clear " ) : ) <$> getCustomPkgDbStack
let progOpts =
2015-08-28 07:44:20 +00:00
[ " --with-ghc= " ++ T . ghcProgram progs ]
2015-08-19 07:04:25 +00:00
-- Only pass ghc-pkg if it was actually set otherwise we
-- might break cabal's guessing logic
2015-09-01 08:27:12 +00:00
++ if T . ghcPkgProgram progs /= T . ghcPkgProgram ( optPrograms defaultOptions )
2015-08-28 07:44:20 +00:00
then [ " --with-ghc-pkg= " ++ T . ghcPkgProgram progs ]
2015-08-19 07:04:25 +00:00
else []
++ map pkgDbArg cusPkgStack
2015-08-28 07:44:20 +00:00
liftIO $ void $ readProc ( T . cabalProgram progs ) ( " configure " : progOpts ) " "
2015-09-02 02:57:25 +00:00
writeAutogen projdir distdir
2015-08-19 07:04:25 +00:00
2015-08-28 07:44:20 +00:00
stackReconfigure crdl progs = do
2015-09-02 02:57:25 +00:00
let projdir = cradleRootDir crdl
distdir = projdir </> cradleDistDir crdl
2015-08-28 07:44:20 +00:00
withDirectory_ ( cradleRootDir crdl ) $ do
supported <- haveStackSupport
if supported
then do
spawn [ T . stackProgram progs , " build " , " --only-dependencies " ]
spawn [ T . stackProgram progs , " build " , " --only-configure " ]
2015-09-02 02:57:25 +00:00
writeAutogen projdir distdir
2015-08-28 07:44:20 +00:00
else
gmLog GmWarning " " $ strDoc $ " Stack project configuration is out of date, please reconfigure manually using 'stack build' as your stack version is too old (need at least 1.4.0.0) "
spawn [] = return ()
spawn ( exe : args ) = do
readProc <- gmReadProcess
liftIO $ void $ readProc exe args " "
haveStackSupport = do
( rv , _ , _ ) <-
liftIO $ readProcessWithExitCode " stack " [ " --numeric-version " ] " "
case rv of
ExitSuccess -> return True
ExitFailure _ -> return False
2015-08-19 07:04:25 +00:00
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
2015-08-07 04:47:34 +00:00
-- * Neither file exists -> should return False:
-- @Nothing < Nothing = False@
-- (since we don't need to @cabal configure@ when no cabal file exists.)
--
2015-08-19 06:46:56 +00:00
-- * Cabal file doesn't exist (impossible since cabal-helper is only used with
-- cabal projects) -> should return False
2015-08-07 04:47:34 +00:00
-- @Just cc < Nothing = False@
--
-- * 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
2015-08-28 07:44:20 +00:00
helperProgs :: Programs -> CH . Programs
helperProgs progs = CH . Programs {
cabalProgram = T . cabalProgram progs ,
ghcProgram = T . ghcProgram progs ,
ghcPkgProgram = T . ghcPkgProgram progs
}
2015-08-07 04:47:34 +00:00
2015-09-01 08:27:12 +00:00
chCached :: ( Applicative m , IOish m , Gm m , Serialize a )
2015-08-18 09:41:14 +00:00
=> ( FilePath -> Cached m GhcModState ChCacheData a ) -> m a
2015-08-07 04:47:34 +00:00
chCached c = do
root <- cradleRootDir <$> cradle
2015-08-18 09:41:14 +00:00
dist <- cradleDistDir <$> cradle
2015-08-19 04:48:27 +00:00
d <- cacheInputData root
2015-08-18 09:41:14 +00:00
withCabal $ cached root ( c dist ) d
2015-08-07 04:47:34 +00:00
where
2015-08-19 04:48:27 +00:00
-- 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
2015-08-31 05:33:36 +00:00
opts <- options
2015-08-28 07:44:20 +00:00
crdl <- cradle
2015-09-01 08:27:12 +00:00
progs' <- patchStackPrograms crdl ( optPrograms opts )
2015-08-31 05:33:36 +00:00
return $ ( helperProgs progs'
2015-08-10 07:07:41 +00:00
, root
2015-08-07 04:47:34 +00:00
, ( gmVer , chVer )
)
gmVer = GhcMod . version
chVer = VERSION_cabal_helper