2015-03-03 19:28:34 +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/>.
2014-07-18 05:05:20 +00:00
2015-03-03 20:12:43 +00:00
{- # LANGUAGE CPP, ViewPatterns, NamedFieldPuns, RankNTypes # -}
module Language.Haskell.GhcMod.Target where
import Control.Arrow
2015-05-17 20:22:56 +00:00
import Control.Applicative ( Applicative , ( <$> ) )
2015-03-03 20:12:43 +00:00
import Control.Monad.Reader ( runReaderT )
import GHC
import GHC.Paths ( libdir )
import StaticFlags
import SysTools
import DynFlags
import HscMain
import HscTypes
2014-07-18 05:05:20 +00:00
import Language.Haskell.GhcMod.DynFlags
2015-03-03 20:12:43 +00:00
import Language.Haskell.GhcMod.Monad.Types
import Language.Haskell.GhcMod.CabalHelper
import Language.Haskell.GhcMod.HomeModuleGraph
2015-03-28 01:30:51 +00:00
import Language.Haskell.GhcMod.PathsAndFiles
2015-03-03 20:12:43 +00:00
import Language.Haskell.GhcMod.GhcPkg
import Language.Haskell.GhcMod.Error
import Language.Haskell.GhcMod.Logging
import Language.Haskell.GhcMod.Types
2015-05-20 10:05:22 +00:00
import Language.Haskell.GhcMod.Utils
2015-03-03 20:12:43 +00:00
import Data.Maybe
2015-05-20 10:05:22 +00:00
import Data.Monoid
2015-03-03 20:12:43 +00:00
import Data.Either
import Data.Foldable ( foldrM )
2015-04-12 01:03:37 +00:00
import Data.Traversable ( traverse )
2015-03-03 20:12:43 +00:00
import Data.IORef
2015-03-05 15:50:06 +00:00
import Data.Map ( Map )
import qualified Data.Map as Map
2015-03-03 20:12:43 +00:00
import Data.Set ( Set )
import qualified Data.Set as Set
2015-03-15 19:48:55 +00:00
import Distribution.Helper
2015-03-03 20:12:43 +00:00
import System.Directory
import System.FilePath
withLightHscEnv :: forall m a . IOish m
=> [ GHCOption ] -> ( HscEnv -> m a ) -> m a
2015-03-05 15:50:06 +00:00
withLightHscEnv opts action = gbracket initEnv teardownEnv action
2015-03-03 20:12:43 +00:00
where
teardownEnv :: HscEnv -> m ()
teardownEnv env = liftIO $ do
let dflags = hsc_dflags env
cleanTempFiles dflags
cleanTempDirs dflags
initEnv :: m HscEnv
initEnv = liftIO $ do
initStaticOpts
settings <- initSysTools ( Just libdir )
dflags <- initDynFlags ( defaultDynFlags settings )
env <- newHscEnv dflags
dflags' <- runLightGhc env $ do
-- HomeModuleGraph and probably all other clients get into all sorts of
-- trouble if the package state isn't initialized here
_ <- setSessionDynFlags =<< getSessionDynFlags
addCmdOpts opts =<< getSessionDynFlags
newHscEnv dflags'
runLightGhc :: HscEnv -> LightGhc a -> IO a
runLightGhc env action = do
renv <- newIORef env
flip runReaderT renv $ unLightGhc action
2015-05-05 12:44:42 +00:00
runGmPkgGhc :: ( IOish m , GmEnv m , GmLog m ) => LightGhc a -> m a
2015-03-03 20:12:43 +00:00
runGmPkgGhc action = do
pkgOpts <- packageGhcOptions
withLightHscEnv pkgOpts $ \ env -> liftIO $ runLightGhc env action
initSession :: IOish m
=> [ GHCOption ] -> ( DynFlags -> Ghc DynFlags ) -> GhcModT m ()
initSession opts mdf = do
s <- gmsGet
case gmGhcSession s of
2015-04-29 16:44:21 +00:00
Just GmGhcSession { .. } -> when ( gmgsOptions /= opts ) $ putNewSession s
Nothing -> putNewSession s
2015-03-03 20:12:43 +00:00
2015-04-29 16:44:21 +00:00
where
putNewSession s = do
rghc <- ( liftIO . newIORef =<< newSession =<< cradle )
gmsPut s { gmGhcSession = Just $ GmGhcSession opts rghc }
newSession Cradle { cradleTempDir } = liftIO $ do
runGhc ( Just libdir ) $ do
let setDf df = setTmpDir cradleTempDir <$> ( mdf =<< addCmdOpts opts df )
_ <- setSessionDynFlags =<< setDf =<< getSessionDynFlags
getSession
dropSession :: IOish m => GhcModT m ()
dropSession = do
s <- gmsGet
case gmGhcSession s of
Just ( GmGhcSession _opts ref ) -> do
-- TODO: This is still not enough, there seem to still be references to
-- GHC's state around afterwards.
liftIO $ writeIORef ref ( error " HscEnv: session was dropped " )
2015-05-07 22:06:08 +00:00
-- Not available on ghc<7.8; didn't really help anyways
-- liftIO $ setUnsafeGlobalDynFlags (error "DynFlags: session was dropped")
2015-04-29 16:44:21 +00:00
Nothing -> return ()
gmsPut s { gmGhcSession = Nothing }
2015-03-03 20:12:43 +00:00
2015-03-09 21:04:04 +00:00
runGmlT :: IOish m => [ Either FilePath ModuleName ] -> GmlT m a -> GhcModT m a
runGmlT fns action = runGmlT' fns return action
2015-03-03 20:12:43 +00:00
2015-03-09 21:04:04 +00:00
runGmlT' :: IOish m
2015-03-03 20:12:43 +00:00
=> [ Either FilePath ModuleName ]
-> ( DynFlags -> Ghc DynFlags )
2015-03-09 21:04:04 +00:00
-> GmlT m a
2015-03-03 20:12:43 +00:00
-> GhcModT m a
2015-03-09 21:04:04 +00:00
runGmlT' fns mdf action = runGmlTWith fns mdf id action
2015-03-03 20:12:43 +00:00
2015-03-09 21:04:04 +00:00
runGmlTWith :: IOish m
2015-03-03 20:12:43 +00:00
=> [ Either FilePath ModuleName ]
-> ( DynFlags -> Ghc DynFlags )
2015-03-09 21:04:04 +00:00
-> ( GmlT m a -> GmlT m b )
-> GmlT m a
2015-03-03 20:12:43 +00:00
-> GhcModT m b
2015-03-09 21:04:04 +00:00
runGmlTWith efnmns' mdf wrapper action = do
2015-03-03 20:12:43 +00:00
crdl <- cradle
Options { ghcUserOptions } <- options
let ( fns , mns ) = partitionEithers efnmns'
ccfns = map ( cradleCurrentDir crdl </> ) fns
cfns <- liftIO $ mapM canonicalizePath ccfns
2015-04-11 14:41:17 +00:00
let serfnmn = Set . fromList $ map Right mns ++ map Left cfns
2015-03-03 20:12:43 +00:00
opts <- targetGhcOptions crdl serfnmn
2015-04-29 15:21:37 +00:00
let opts' = opts ++ [ " -O0 " ] ++ ghcUserOptions
2015-03-03 20:12:43 +00:00
initSession opts' $
setModeSimple >>> setEmptyLogger >>> mdf
2015-04-11 14:41:17 +00:00
let rfns = map ( makeRelative $ cradleRootDir crdl ) cfns
2015-03-09 21:04:04 +00:00
unGmlT $ wrapper $ do
2015-03-03 20:12:43 +00:00
loadTargets ( map moduleNameString mns ++ rfns )
action
2015-03-28 01:30:51 +00:00
targetGhcOptions :: forall m . IOish m
2015-03-03 20:12:43 +00:00
=> Cradle
-> Set ( Either FilePath ModuleName )
-> GhcModT m [ GHCOption ]
targetGhcOptions crdl sefnmn = do
when ( Set . null sefnmn ) $ error " targetGhcOptions: no targets given "
case cradleCabalFile crdl of
2015-03-28 01:30:51 +00:00
Just _ -> cabalOpts crdl
2015-03-03 20:12:43 +00:00
Nothing -> sandboxOpts crdl
where
zipMap f l = l ` zip ` ( f ` map ` l )
2015-03-28 01:30:51 +00:00
cabalOpts :: Cradle -> GhcModT m [ String ]
cabalOpts Cradle { .. } = do
comps <- mapM ( resolveEntrypoint crdl ) =<< getComponents
mcs <- cached cradleRootDir resolvedComponentsCache comps
2015-03-03 20:12:43 +00:00
let mdlcs = moduleComponents mcs ` zipMap ` Set . toList sefnmn
2015-04-12 00:40:39 +00:00
candidates = findCandidates $ map snd mdlcs
2015-03-03 20:12:43 +00:00
2015-03-08 16:32:17 +00:00
let noCandidates = Set . null candidates
noModuleHasAnyAssignment = all ( Set . null . snd ) mdlcs
if noCandidates && noModuleHasAnyAssignment
then do
2015-05-17 20:17:56 +00:00
gmLog GmWarning " " $ strDoc $ " Could not find a component assignment, falling back to sandbox only project options. "
2015-03-08 16:32:17 +00:00
sandboxOpts crdl
else do
when noCandidates $
throwError $ GMECabalCompAssignment mdlcs
let cn = pickComponent candidates
return $ gmcGhcOpts $ fromJust $ Map . lookup cn mcs
2015-03-03 20:12:43 +00:00
2015-03-28 01:30:51 +00:00
resolvedComponentsCache :: IOish m => Cached ( GhcModT m )
2015-04-12 00:39:18 +00:00
[ GmComponent GMCRaw ( Set . Set ModulePath ) ]
2015-03-28 01:30:51 +00:00
( Map . Map ChComponentName ( GmComponent GMCResolved ( Set . Set ModulePath ) ) )
resolvedComponentsCache = Cached {
cacheFile = resolvedComponentsCacheFile ,
2015-04-12 00:39:18 +00:00
cachedAction = \ tcfs comps ma -> do
2015-03-28 01:30:51 +00:00
Cradle { .. } <- cradle
2015-04-12 00:39:18 +00:00
let mums =
case invalidatingInputFiles tcfs of
Nothing -> Nothing
Just iifs ->
let
filterOutSetupCfg =
filter ( /= cradleRootDir </> setupConfigPath )
changedFiles = filterOutSetupCfg iifs
in if null changedFiles
then Nothing
else Just $ map Left changedFiles
case ma of
Just mcs -> gmsGet >>= \ s -> gmsPut s { gmComponents = mcs }
Nothing -> return ()
-- liftIO $ print ("changed files", mums :: Maybe [Either FilePath ()])
2015-03-28 01:30:51 +00:00
mcs <- resolveGmComponents mums comps
return ( setupConfigPath : flatten mcs , mcs )
}
where
flatten :: Map . Map ChComponentName ( GmComponent t ( Set . Set ModulePath ) )
-> [ FilePath ]
flatten = Map . elems
>>> map ( gmcHomeModuleGraph >>> gmgGraph
>>> Map . elems
>>> map ( Set . map mpPath )
>>> Set . unions
)
>>> Set . unions
>>> Set . toList
moduleComponents :: Map ChComponentName ( GmComponent t ( Set ModulePath ) )
2015-03-03 20:12:43 +00:00
-> Either FilePath ModuleName
2015-03-15 19:48:55 +00:00
-> Set ChComponentName
2015-03-03 20:12:43 +00:00
moduleComponents m efnmn =
foldr' Set . empty m $ \ c s ->
let
memb =
case efnmn of
Left fn -> fn ` Set . member ` Set . map mpPath ( smp c )
Right mn -> mn ` Set . member ` Set . map mpModule ( smp c )
in if memb
then Set . insert ( gmcName c ) s
else s
where
smp c = Map . keysSet $ gmgGraph $ gmcHomeModuleGraph c
foldr' b as f = Map . foldr f b as
2015-04-12 00:40:39 +00:00
findCandidates :: [ Set ChComponentName ] -> Set ChComponentName
findCandidates [] = Set . empty
findCandidates scns = foldl1 Set . intersection scns
2015-03-15 19:48:55 +00:00
pickComponent :: Set ChComponentName -> ChComponentName
2015-03-03 20:12:43 +00:00
pickComponent scn = Set . findMin scn
2015-05-17 20:22:56 +00:00
packageGhcOptions :: ( Applicative m , MonadIO m , GmEnv m , GmLog m ) => m [ GHCOption ]
2015-03-03 20:12:43 +00:00
packageGhcOptions = do
crdl <- cradle
case cradleCabalFile crdl of
2015-05-17 20:22:56 +00:00
Just _ ->
2015-03-03 20:12:43 +00:00
( Set . toList . Set . fromList . concat . map snd ) ` liftM ` getGhcPkgOptions
Nothing -> sandboxOpts crdl
sandboxOpts :: Monad m => Cradle -> m [ String ]
2015-03-28 01:30:51 +00:00
sandboxOpts crdl =
return $ [ " -i " ++ d | d <- [ wdir , rdir ] ] ++ pkgOpts ++ [ " -Wall " ]
2015-03-03 20:12:43 +00:00
where
pkgOpts = ghcDbStackOpts $ cradlePkgDbStack crdl
( wdir , rdir ) = ( cradleCurrentDir crdl , cradleRootDir crdl )
resolveGmComponent :: ( IOish m , GmLog m , GmEnv m )
=> Maybe [ Either FilePath ModuleName ] -- ^ Updated modules
2015-03-28 01:30:51 +00:00
-> GmComponent GMCRaw ( Set ModulePath )
-> m ( GmComponent GMCResolved ( Set ModulePath ) )
resolveGmComponent mums c @ GmComponent { .. } = do
2015-04-12 00:36:17 +00:00
withLightHscEnv ghcOpts $ \ env -> do
2015-03-28 01:30:51 +00:00
let srcDirs = if null gmcSourceDirs then [ " " ] else gmcSourceDirs
let mg = gmcHomeModuleGraph
let simp = gmcEntrypoints
sump <- case mums of
2015-03-03 20:12:43 +00:00
Nothing -> return simp
2015-04-12 00:36:17 +00:00
Just ums ->
Set . fromList . catMaybes <$>
mapM ( resolveModule env srcDirs ) ums
2015-03-03 20:12:43 +00:00
2015-04-11 14:41:17 +00:00
mg' <- canonicalizeModuleGraph =<< updateHomeModuleGraph env mg simp sump
2015-03-03 20:12:43 +00:00
return $ c { gmcEntrypoints = simp , gmcHomeModuleGraph = mg' }
2015-04-12 00:36:17 +00:00
where ghcOpts = concat [
gmcGhcSrcOpts ,
gmcGhcLangOpts ,
[ " -optP-include " , " -optP " ++ macrosHeaderPath ]
]
2015-03-28 01:30:51 +00:00
resolveEntrypoint :: IOish m
=> Cradle
-> GmComponent GMCRaw ChEntrypoint
-> m ( GmComponent GMCRaw ( Set ModulePath ) )
resolveEntrypoint Cradle { .. } c @ GmComponent { .. } =
withLightHscEnv gmcGhcSrcOpts $ \ env -> do
let srcDirs = if null gmcSourceDirs then [ " " ] else gmcSourceDirs
eps <- liftIO $ resolveChEntrypoints cradleRootDir gmcEntrypoints
rms <- resolveModule env srcDirs ` mapM ` eps
return c { gmcEntrypoints = Set . fromList $ catMaybes rms }
resolveModule :: MonadIO m =>
HscEnv -> [ FilePath ] -> Either FilePath ModuleName -> m ( Maybe ModulePath )
2015-04-11 14:41:17 +00:00
resolveModule env _srcDirs ( Right mn ) =
liftIO $ traverse canonicalizeModulePath =<< findModulePath env mn
2015-03-28 01:30:51 +00:00
resolveModule env srcDirs ( Left fn' ) = liftIO $ do
2015-05-20 10:05:22 +00:00
mfn <- findFile' srcDirs fn'
2015-03-28 01:30:51 +00:00
case mfn of
Nothing -> return Nothing
Just fn'' -> do
2015-04-11 14:41:17 +00:00
fn <- canonicalizePath fn''
2015-03-28 01:30:51 +00:00
emn <- fileModuleName env fn
return $ case emn of
Left _ -> Nothing
Right mmn -> Just $
case mmn of
Nothing -> mkMainModulePath fn
Just mn -> ModulePath mn fn
2015-05-20 10:05:22 +00:00
where
findFile' dirs file =
getFirst . mconcat <$> mapM ( fmap First . mightExist . ( </> file ) ) dirs
2015-03-03 20:12:43 +00:00
2015-03-15 19:48:55 +00:00
resolveChEntrypoints ::
FilePath -> ChEntrypoint -> IO [ Either FilePath ModuleName ]
resolveChEntrypoints _ ( ChLibEntrypoint em om ) =
return $ map ( Right . chModToMod ) ( em ++ om )
resolveChEntrypoints _ ( ChExeEntrypoint main om ) =
return $ [ Left main ] ++ map ( Right . chModToMod ) om
resolveChEntrypoints srcDir ChSetupEntrypoint = do
shs <- doesFileExist ( srcDir </> " Setup.hs " )
slhs <- doesFileExist ( srcDir </> " Setup.lhs " )
return $ case ( shs , slhs ) of
( True , _ ) -> [ Left " Setup.hs " ]
( _ , True ) -> [ Left " Setup.lhs " ]
( False , False ) -> []
chModToMod :: ChModuleName -> ModuleName
chModToMod ( ChModuleName mn ) = mkModuleName mn
2015-03-28 01:30:51 +00:00
resolveGmComponents :: ( IOish m , GmState m , GmLog m , GmEnv m ) =>
Maybe [ Either FilePath ModuleName ]
-- ^ Updated modules
-> [ GmComponent GMCRaw ( Set ModulePath ) ]
-> m ( Map ChComponentName ( GmComponent GMCResolved ( Set ModulePath ) ) )
2015-03-03 20:12:43 +00:00
resolveGmComponents mumns cs = do
s <- gmsGet
m' <- foldrM' ( gmComponents s ) cs $ \ c m -> do
case Map . lookup ( gmcName c ) m of
Nothing -> insertUpdated m c
Just c' -> if same gmcRawEntrypoints c c' && same gmcGhcSrcOpts c c'
then return m
else insertUpdated m c
gmsPut s { gmComponents = m' }
return m'
2015-05-20 10:05:22 +00:00
2015-03-03 20:12:43 +00:00
where
foldrM' b fa f = foldrM f b fa
insertUpdated m c = do
rc <- resolveGmComponent mumns c
return $ Map . insert ( gmcName rc ) rc m
same :: Eq b
2015-03-28 01:30:51 +00:00
=> ( forall t a . GmComponent t a -> b )
-> GmComponent u c -> GmComponent v d -> Bool
2015-03-03 20:12:43 +00:00
same f a b = ( f a ) == ( f b )
2014-07-18 05:05:20 +00:00
-- | Set the files as targets and load them.
2015-03-09 21:04:04 +00:00
loadTargets :: IOish m => [ String ] -> GmlT m ()
2015-03-03 20:12:43 +00:00
loadTargets filesOrModules = do
gmLog GmDebug " loadTargets " $
text " Loading " <+>: fsep ( map text filesOrModules )
targets <- forM filesOrModules ( flip guessTarget Nothing )
setTargets targets
2014-08-12 16:09:31 +00:00
mode <- getCompilerMode
2015-03-03 20:12:43 +00:00
if mode == Intelligent
then loadTargets' Intelligent
2014-07-19 02:53:05 +00:00
else do
2015-03-03 20:12:43 +00:00
mdls <- depanal [] False
2014-07-19 02:53:05 +00:00
let fallback = needsFallback mdls
if fallback then do
resetTargets targets
setIntelligent
2015-03-03 20:12:43 +00:00
gmLog GmInfo " loadTargets " $
2015-04-29 15:22:48 +00:00
text " Target needs interpeter, switching to LinkInMemory/HscInterpreted. Perfectly normal if anything is using TemplateHaskell, QuasiQuotes or PatternSynonyms. "
2015-03-03 20:12:43 +00:00
loadTargets' Intelligent
2014-07-19 02:53:05 +00:00
else
2015-03-03 20:12:43 +00:00
loadTargets' Simple
2014-07-18 05:05:20 +00:00
where
2015-03-03 20:12:43 +00:00
loadTargets' Simple = do
void $ load LoadAllTargets
loadTargets' Intelligent = do
df <- getSessionDynFlags
void $ setSessionDynFlags ( setModeIntelligent df )
void $ load LoadAllTargets
2014-07-19 02:53:05 +00:00
resetTargets targets = do
2015-03-03 20:12:43 +00:00
setTargets []
void $ load LoadAllTargets
setTargets targets
2014-07-19 02:53:05 +00:00
setIntelligent = do
2015-03-03 20:12:43 +00:00
newdf <- setModeIntelligent <$> getSessionDynFlags
void $ setSessionDynFlags newdf
2014-07-22 17:45:48 +00:00
setCompilerMode Intelligent
2014-07-18 05:05:20 +00:00
2015-03-03 20:12:43 +00:00
needsFallback :: ModuleGraph -> Bool
2014-09-12 01:48:22 +00:00
needsFallback = any $ \ ms ->
2015-03-03 20:12:43 +00:00
let df = ms_hspp_opts ms in
2014-09-12 01:48:22 +00:00
Opt_TemplateHaskell ` xopt ` df
|| Opt_QuasiQuotes ` xopt ` df
# if __GLASGOW_HASKELL__ >= 708
|| ( Opt_PatternSynonyms ` xopt ` df )
# endif