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-14 01:48:29 +00:00
, prepareCabalHelper
2015-09-23 10:01:37 +00:00
, withAutogen
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-11-18 19:51:37 +00:00
import Data.Version
import Data.Binary ( Binary )
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-09-07 01:49:12 +00:00
import Language.Haskell.GhcMod.CustomPackageDb
2015-09-15 03:25:00 +00:00
import Language.Haskell.GhcMod.Stack
2015-03-03 20:12:43 +00:00
import System.FilePath
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 ,
2015-09-07 03:15:29 +00:00
cachedAction = \ _tcf ( _progs , _projdir , _ver ) _ma -> do
2015-11-26 15:19:50 +00:00
opts <- runCHQuery 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 ,
2015-09-07 03:15:29 +00:00
cachedAction = \ _tcf ( _progs , _projdir , _ver ) _ma -> do
2015-08-19 06:46:56 +00:00
crdl <- cradle
2015-11-26 15:19:50 +00:00
dbs <- map chPkgToGhcPkg <$>
2015-09-07 03:15:29 +00:00
runCHQuery 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-09-23 10:01:37 +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 ,
2015-09-07 03:15:29 +00:00
cachedAction = \ _tcf ( _progs , _projdir , _ver ) _ma -> do
runCHQuery $ 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'
]
2016-01-10 21:01:33 +00:00
getQueryEnv :: ( IOish m , GmOut m , GmEnv m ) => m QueryEnv
getQueryEnv = do
2015-09-07 03:15:29 +00:00
crdl <- cradle
2016-01-10 21:01:33 +00:00
progs <- patchStackPrograms crdl =<< ( optPrograms <$> options )
readProc <- gmReadProcess
2015-09-07 03:15:29 +00:00
let projdir = cradleRootDir crdl
distdir = projdir </> cradleDistDir crdl
2016-01-10 21:01:33 +00:00
return ( defaultQueryEnv projdir distdir ) {
qeReadProcess = readProc
, qePrograms = helperProgs progs
}
2015-09-07 03:15:29 +00:00
2016-01-10 21:01:33 +00:00
runCHQuery :: ( IOish m , GmOut m , GmEnv m ) => Query m b -> m b
runCHQuery a = do
qe <- getQueryEnv
2015-09-07 03:15:29 +00:00
runQuery qe 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
2015-09-11 01:48:52 +00:00
when ( isCabalHelperProject $ cradleProject crdl ) $
2016-01-10 21:01:33 +00:00
withCabal $ prepare' =<< getQueryEnv
2015-08-14 01:48:29 +00:00
2015-09-23 10:01:37 +00:00
withAutogen :: ( IOish m , GmEnv m , GmOut m , GmLog m ) => m a -> m a
withAutogen action = do
gmLog GmDebug " " $ strDoc $ " making sure autogen files exist "
crdl <- cradle
let projdir = cradleRootDir crdl
distdir = projdir </> cradleDistDir crdl
2015-09-24 02:49:49 +00:00
( pkgName' , _ ) <- runCHQuery packageId
2015-09-23 10:01:37 +00:00
mCabalFile <- liftIO $ timeFile ` traverse ` cradleCabalFile crdl
mCabalMacroHeader <- liftIO $ timeMaybe ( distdir </> macrosHeaderPath )
mCabalPathsModule <- liftIO $ timeMaybe ( distdir </> autogenModulePath pkgName' )
when ( mCabalMacroHeader < mCabalFile || mCabalPathsModule < mCabalFile ) $ do
gmLog GmDebug " " $ strDoc $ " autogen files out of sync "
2016-01-10 21:01:33 +00:00
writeAutogen
2015-09-23 10:01:37 +00:00
action
where
2016-01-10 21:01:33 +00:00
writeAutogen = do
2015-09-23 10:01:37 +00:00
gmLog GmDebug " " $ strDoc $ " writing Cabal autogen files "
2016-01-10 21:01:33 +00:00
writeAutogenFiles' =<< getQueryEnv
2015-09-23 10:01:37 +00:00
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-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
2015-09-24 03:27:20 +00:00
let haveSetupConfig = isJust mCabalConfig
2015-09-24 02:49:49 +00:00
cusPkgDb <- getCustomPkgDbStack
2015-09-24 03:27:20 +00:00
( flgs , pkgDbStackOutOfSync ) <- do
if haveSetupConfig
2015-09-24 02:49:49 +00:00
then runCHQuery $ do
2015-09-24 03:27:20 +00:00
flgs <- nonDefaultConfigFlags
2015-09-24 02:49:49 +00:00
pkgDb <- map chPkgToGhcPkg <$> packageDbStack
2015-09-24 03:27:20 +00:00
return ( flgs , fromMaybe False $ ( pkgDb /= ) <$> cusPkgDb )
else return ( [] , False )
2015-08-11 04:35:14 +00:00
2015-08-07 04:47:34 +00:00
when ( isSetupConfigOutOfDate mCabalFile mCabalConfig ) $
2015-09-23 10:01:37 +00:00
gmLog GmDebug " " $ strDoc $ " setup configuration is out of date "
2015-08-19 06:46:56 +00:00
when ( isSetupConfigOutOfDate mCabalSandboxConfig mCabalConfig ) $
2015-09-23 10:01:37 +00:00
gmLog GmDebug " " $ strDoc $ " sandbox configuration is out of date "
2015-08-19 06:46:56 +00:00
2015-08-07 04:47:34 +00:00
when pkgDbStackOutOfSync $
2015-09-23 10:01:37 +00:00
gmLog GmDebug " " $ strDoc $ " package-db stack out of sync with ghc-mod.package-db-stack "
2015-08-07 04:47:34 +00:00
2015-08-19 06:46:56 +00:00
when ( isSetupConfigOutOfDate mCabalFile mCabalConfig
|| pkgDbStackOutOfSync
2015-09-24 02:49:49 +00:00
|| isSetupConfigOutOfDate mCabalSandboxConfig mCabalConfig ) $ do
proj <- cradleProject <$> cradle
opts <- options
2015-09-11 01:48:52 +00:00
case proj of
2015-09-23 10:01:37 +00:00
CabalProject -> do
gmLog GmDebug " " $ strDoc " reconfiguring Cabal project "
2015-09-24 03:27:20 +00:00
cabalReconfigure ( optPrograms opts ) crdl flgs
2015-09-23 10:01:37 +00:00
StackProject { } -> do
gmLog GmDebug " " $ strDoc " reconfiguring Stack project "
2015-09-24 03:27:20 +00:00
-- TODO: we could support flags for stack too, but it seems
-- you're supposed to put those in stack.yaml so detecting which
-- flags to pass down would be more difficult
-- "--flag PACKAGE:[-]FLAG Override flags set in stack.yaml
-- (applies to local packages and extra-deps)"
2016-08-24 15:09:29 +00:00
stackReconfigure ( optStackBuildDeps opts ) crdl ( optPrograms opts )
2015-08-19 07:04:25 +00:00
_ ->
2015-09-11 01:48:52 +00:00
error $ " withCabal: unsupported project type: " ++ show proj
2015-08-19 07:04:25 +00:00
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-24 03:27:20 +00:00
cabalReconfigure progs crdl flgs = do
2015-09-24 02:49:49 +00:00
readProc <- gmReadProcess
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-09-24 03:27:20 +00:00
++ flagOpt
toFlag ( f , True ) = f
toFlag ( f , False ) = '-' : f
flagOpt = [ " --flags " , unwords $ map toFlag flgs ]
2015-08-19 07:04:25 +00:00
2015-09-24 03:27:20 +00:00
liftIO $ void $ readProc ( T . cabalProgram progs ) ( " configure " : progOpts ) " "
2016-08-24 15:09:29 +00:00
stackReconfigure deps crdl progs = do
2015-08-28 07:44:20 +00:00
withDirectory_ ( cradleRootDir crdl ) $ do
supported <- haveStackSupport
if supported
then do
2016-08-24 15:09:29 +00:00
when deps $
spawn [ T . stackProgram progs , " build " , " --only-dependencies " , " . " ]
2015-09-08 01:54:29 +00:00
spawn [ T . stackProgram progs , " build " , " --only-configure " , " . " ]
2015-08-28 07:44:20 +00:00
else
2015-09-02 03:02:13 +00:00
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 0.1.4.0) "
2015-08-28 07:44:20 +00:00
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-11-18 19:51:37 +00:00
chCached :: ( Applicative m , IOish m , Gm m , Binary 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
2015-09-07 03:15:29 +00:00
projdir <- cradleRootDir <$> cradle
distdir <- ( projdir </> ) . cradleDistDir <$> cradle
d <- cacheInputData projdir
withCabal $ cached projdir ( c distdir ) d
2015-08-07 04:47:34 +00:00
where
2015-11-18 19:54:12 +00:00
-- we don't need to include the distdir in the cache input because when it
2015-08-19 04:48:27 +00:00
-- changes the cache files will be gone anyways ;)
2015-09-07 03:15:29 +00:00
cacheInputData projdir = 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-09-07 03:15:29 +00:00
, projdir
2015-11-18 19:51:37 +00:00
, ( showVersion gmVer , chVer )
2015-08-07 04:47:34 +00:00
)
gmVer = GhcMod . version
chVer = VERSION_cabal_helper