{-# LANGUAGE TypeFamilies #-}
module Development.IDE.Session (loadSession) where
import Control.Concurrent.Async
import Control.Concurrent.Extra
import Control.Exception.Safe
import Control.Monad
import Control.Monad.Extra
import Control.Monad.IO.Class
import qualified Crypto.Hash.SHA1 as H
import qualified Data.ByteString.Char8 as B
import qualified Data.HashMap.Strict as HM
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import Data.Aeson
import Data.Bifunctor
import qualified Data.ByteString.Base16 as B16
import Data.Either.Extra
import Data.Function
import Data.Hashable
import Data.List
import Data.IORef
import Data.Maybe
import Data.Time.Clock
import Data.Version
import Development.IDE.Core.OfInterest
import Development.IDE.Core.Shake
import Development.IDE.Core.RuleTypes
import Development.IDE.GHC.Compat
import Development.IDE.GHC.Util
import Development.IDE.Session.VersionCheck
import Development.IDE.Types.Diagnostics
import Development.IDE.Types.Exports
import Development.IDE.Types.Location
import Development.IDE.Types.Logger
import Development.IDE.Types.Options
import Development.Shake (Action)
import GHC.Check
import HIE.Bios
import HIE.Bios.Environment hiding (getCacheDir)
import HIE.Bios.Types
import Hie.Implicit.Cradle (loadImplicitHieCradle)
import Language.Haskell.LSP.Core
import Language.Haskell.LSP.Messages
import Language.Haskell.LSP.Types
import System.Directory
import qualified System.Directory.Extra as IO
import System.FilePath
import System.Info
import System.IO
import GHCi
import DynFlags
import HscTypes
import Linker
import Module
import NameCache
import Packages
import Control.Exception (evaluate)
import Data.Char
loadSession :: FilePath -> IO (Action IdeGhcSession)
loadSession dir = do
hscEnvs <- newVar Map.empty :: IO (Var HieMap)
fileToFlags <- newVar Map.empty :: IO (Var FlagsMap)
version <- newVar 0
let returnWithVersion fun = IdeGhcSession fun <$> liftIO (readVar version)
let invalidateShakeCache = do
modifyVar_ version (return . succ)
cradleLoc <- liftIO $ memoIO $ \v -> do
res <- findCradle v
res' <- traverse makeAbsolute res
return $ normalise <$> res'
dummyAs <- async $ return (error "Uninitialised")
runningCradle <- newVar dummyAs :: IO (Var (Async (IdeResult HscEnvEq,[FilePath])))
return $ do
extras@ShakeExtras{logger, eventer, restartShakeSession,
withIndefiniteProgress, ideNc, knownTargetsVar
} <- getShakeExtras
IdeOptions{ optTesting = IdeTesting optTesting
, optCheckProject = CheckProject checkProject
, optCustomDynFlags
} <- getIdeOptions
let extendKnownTargets newTargets = do
knownTargets <- forM newTargets $ \TargetDetails{..} -> do
found <- filterM (IO.doesFileExist . fromNormalizedFilePath) targetLocations
return (targetModule, found)
modifyVar_ knownTargetsVar $ traverseHashed $ \known -> do
let known' = HM.unionWith (<>) known $ HM.fromList knownTargets
when (known /= known') $
logDebug logger $ "Known files updated: " <>
T.pack(show $ (HM.map . map) fromNormalizedFilePath known')
evaluate known'
let packageSetup :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
packageSetup (hieYaml, cfp, opts, libDir) = do
hscEnv <- emptyHscEnv ideNc libDir
(df, targets) <- evalGhcEnv hscEnv $
first optCustomDynFlags <$> setOptions opts (hsc_dflags hscEnv)
let deps = componentDependencies opts ++ maybeToList hieYaml
dep_info <- getDependencyInfo deps
modifyVar hscEnvs $ \m -> do
let oldDeps = Map.lookup hieYaml m
let
new_deps = RawComponentInfo (thisInstalledUnitId df) df targets cfp opts dep_info
: maybe [] snd oldDeps
inplace = map rawComponentUnitId new_deps
new_deps' <- forM new_deps $ \RawComponentInfo{..} -> do
let (df2, uids) = removeInplacePackages inplace rawComponentDynFlags
let prefix = show rawComponentUnitId
processed_df <- setCacheDir logger prefix (sort $ map show uids) opts df2
pure $ ComponentInfo rawComponentUnitId
processed_df
uids
rawComponentTargets
rawComponentFP
rawComponentCOptions
rawComponentDependencyInfo
logInfo logger (T.pack ("Making new HscEnv" ++ show inplace))
hscEnv <- emptyHscEnv ideNc libDir
newHscEnv <-
evalGhcEnv hscEnv $ do
_ <- setSessionDynFlags df
getSession
pure (Map.insert hieYaml (newHscEnv, new_deps) m, (newHscEnv, head new_deps', tail new_deps'))
let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
-> IO ([NormalizedFilePath],(IdeResult HscEnvEq,[FilePath]))
session args@(hieYaml, _cfp, _opts, _libDir) = do
(hscEnv, new, old_deps) <- packageSetup args
when (os == "linux") $ do
initObjLinker hscEnv
res <- loadDLL hscEnv "libm.so.6"
case res of
Nothing -> pure ()
Just err -> hPutStrLn stderr $
"Error dynamically loading libm.so.6:\n" <> err
let uids = map (\ci -> (componentUnitId ci, componentDynFlags ci)) (new : old_deps)
let new_cache = newComponentCache logger hieYaml hscEnv uids
(cs, res) <- new_cache new
cached_targets <- concatMapM (fmap fst . new_cache) old_deps
let all_targets = cs ++ cached_targets
modifyVar_ fileToFlags $ \var -> do
pure $ Map.insert hieYaml (HM.fromList (concatMap toFlagsMap all_targets)) var
extendKnownTargets all_targets
invalidateShakeCache
restartShakeSession [kick]
let resultCachedTargets = concatMap targetLocations all_targets
return (resultCachedTargets, second Map.keys res)
let consultCradle :: Maybe FilePath -> FilePath -> IO ([NormalizedFilePath], (IdeResult HscEnvEq, [FilePath]))
consultCradle hieYaml cfp = do
lfp <- flip makeRelative cfp <$> getCurrentDirectory
logInfo logger $ T.pack ("Consulting the cradle for " <> show lfp)
when (isNothing hieYaml) $ eventer $ notifyUserImplicitCradle lfp
cradle <- maybe (loadImplicitHieCradle $ addTrailingPathSeparator dir) loadCradle hieYaml
when optTesting $ eventer $ notifyCradleLoaded lfp
let progMsg = "Setting up " <> T.pack (takeBaseName (cradleRootDir cradle))
<> " (for " <> T.pack lfp <> ")"
eopts <- withIndefiniteProgress progMsg NotCancellable $
cradleToOptsAndLibDir cradle cfp
logDebug logger $ T.pack ("Session loading result: " <> show eopts)
case eopts of
Right (opts, libDir) -> do
installationCheck <- ghcVersionChecker libDir
case installationCheck of
InstallationNotFound{..} ->
error $ "GHC installation not found in libdir: " <> libdir
InstallationMismatch{..} ->
return ([],(([renderPackageSetupException cfp GhcVersionMismatch{..}], Nothing),[]))
InstallationChecked _compileTime _ghcLibCheck ->
session (hieYaml, toNormalizedFilePath' cfp, opts, libDir)
Left err -> do
dep_info <- getDependencyInfo (maybeToList hieYaml)
let ncfp = toNormalizedFilePath' cfp
let res = (map (renderCradleError ncfp) err, Nothing)
modifyVar_ fileToFlags $ \var -> do
pure $ Map.insertWith HM.union hieYaml (HM.singleton ncfp (res, dep_info)) var
return ([ncfp],(res,[]))
let sessionOpts :: (Maybe FilePath, FilePath)
-> IO ([NormalizedFilePath], (IdeResult HscEnvEq, [FilePath]))
sessionOpts (hieYaml, file) = do
v <- fromMaybe HM.empty . Map.lookup hieYaml <$> readVar fileToFlags
cfp <- canonicalizePath file
case HM.lookup (toNormalizedFilePath' cfp) v of
Just (opts, old_di) -> do
deps_ok <- checkDependencyInfo old_di
if not deps_ok
then do
modifyVar_ fileToFlags (const (return Map.empty))
modifyVar_ hscEnvs (return . Map.adjust (\(h, _) -> (h, [])) hieYaml )
consultCradle hieYaml cfp
else return (HM.keys v, (opts, Map.keys old_di))
Nothing -> consultCradle hieYaml cfp
let getOptions :: FilePath -> IO ([NormalizedFilePath],(IdeResult HscEnvEq, [FilePath]))
getOptions file = do
hieYaml <- cradleLoc file
sessionOpts (hieYaml, file) `catch` \e ->
return ([],(([renderPackageSetupException file e], Nothing),[]))
returnWithVersion $ \file -> do
(cs, opts) <- liftIO $ join $ mask_ $ modifyVar runningCradle $ \as -> do
void $ wait as
as <- async $ getOptions file
return (fmap snd as, wait as)
unless (null cs) $ do
cfps' <- liftIO $ filterM (IO.doesFileExist . fromNormalizedFilePath) cs
void $ shakeEnqueue extras $ mkDelayedAction "InitialLoad" Debug $ void $ do
when checkProject $ do
mmt <- uses GetModificationTime cfps'
let cs_exist = catMaybes (zipWith (<$) cfps' mmt)
modIfaces <- uses GetModIface cs_exist
extras <- getShakeExtras
let !exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
liftIO $ modifyVar_ (exportsMap extras) $ evaluate . (exportsMap' <>)
pure opts
cradleToOptsAndLibDir :: Show a => Cradle a -> FilePath
-> IO (Either [CradleError] (ComponentOptions, FilePath))
cradleToOptsAndLibDir cradle file = do
let showLine s = hPutStrLn stderr ("> " ++ s)
hPutStrLn stderr $ "Output from setting up the cradle " <> show cradle
cradleRes <- runCradle (cradleOptsProg cradle) showLine file
case cradleRes of
CradleSuccess r -> do
libDirRes <- getRuntimeGhcLibDir cradle
case libDirRes of
CradleSuccess libDir -> pure (Right (r, libDir))
CradleFail err -> return (Left [err])
CradleNone -> return (Left [])
CradleFail err -> return (Left [err])
CradleNone -> return (Left [])
emptyHscEnv :: IORef NameCache -> FilePath -> IO HscEnv
emptyHscEnv nc libDir = do
env <- runGhc (Just libDir) getSession
initDynLinker env
pure $ setNameCache nc env
data TargetDetails = TargetDetails
{
targetModule :: !ModuleName,
targetEnv :: !(IdeResult HscEnvEq),
targetDepends :: !DependencyInfo,
targetLocations :: ![NormalizedFilePath]
}
fromTargetId :: [FilePath]
-> TargetId
-> IdeResult HscEnvEq
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId is (TargetModule mod) env dep = do
let fps = [i </> moduleNameSlashes mod -<.> ext | ext <- exts, i <- is ]
exts = ["hs", "hs-boot", "lhs"]
locs <- mapM (fmap toNormalizedFilePath' . canonicalizePath) fps
return [TargetDetails mod env dep locs]
fromTargetId _ (TargetFile f _) env deps = do
nf <- toNormalizedFilePath' <$> canonicalizePath f
return [TargetDetails m env deps [nf] | m <- moduleNames f]
moduleNames :: FilePath -> [ModuleName]
moduleNames f = map (mkModuleName .intercalate ".") $ init $ tails nameSegments
where
nameSegments = reverse
$ takeWhile (isUpper . head)
$ reverse
$ splitDirectories
$ dropExtension f
toFlagsMap :: TargetDetails -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap TargetDetails{..} =
[ (l, (targetEnv, targetDepends)) | l <- targetLocations]
setNameCache :: IORef NameCache -> HscEnv -> HscEnv
setNameCache nc hsc = hsc { hsc_NC = nc }
newComponentCache
:: Logger
-> Maybe FilePath
-> HscEnv
-> [(InstalledUnitId, DynFlags)]
-> ComponentInfo
-> IO ( [TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
newComponentCache logger cradlePath hsc_env uids ci = do
let df = componentDynFlags ci
let hscEnv' = hsc_env { hsc_dflags = df
, hsc_IC = (hsc_IC hsc_env) { ic_dflags = df } }
let newFunc = maybe newHscEnvEqPreserveImportPaths newHscEnvEq cradlePath
henv <- newFunc hscEnv' uids
let targetEnv = ([], Just henv)
targetDepends = componentDependencyInfo ci
res = (targetEnv, targetDepends)
logDebug logger ("New Component Cache HscEnvEq: " <> T.pack (show res))
let mk t = fromTargetId (importPaths df) (targetId t) targetEnv targetDepends
ctargets <- concatMapM mk (componentTargets ci)
let special_target = TargetDetails (mkModuleName "special") targetEnv targetDepends [componentFP ci]
return (special_target:ctargets, res)
setCacheDir :: MonadIO m => Logger -> String -> [String] -> ComponentOptions -> DynFlags -> m DynFlags
setCacheDir logger prefix hscComponents comps dflags = do
cacheDir <- liftIO $ getCacheDir prefix (hscComponents ++ componentOptions comps)
liftIO $ logInfo logger $ "Using interface files cache dir: " <> T.pack cacheDir
pure $ dflags
& setHiDir cacheDir
& setHieDir cacheDir
renderCradleError :: NormalizedFilePath -> CradleError -> FileDiagnostic
renderCradleError nfp (CradleError _ _ec t) =
ideErrorWithSource (Just "cradle") (Just DsError) nfp (T.unlines (map T.pack t))
type DependencyInfo = Map.Map FilePath (Maybe UTCTime)
type HieMap = Map.Map (Maybe FilePath) (HscEnv, [RawComponentInfo])
type FlagsMap = Map.Map (Maybe FilePath) (HM.HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
data RawComponentInfo = RawComponentInfo
{ rawComponentUnitId :: InstalledUnitId
, rawComponentDynFlags :: DynFlags
, rawComponentTargets :: [Target]
, rawComponentFP :: NormalizedFilePath
, rawComponentCOptions :: ComponentOptions
, rawComponentDependencyInfo :: DependencyInfo
}
data ComponentInfo = ComponentInfo
{ componentUnitId :: InstalledUnitId
, componentDynFlags :: DynFlags
, _componentInternalUnits :: [InstalledUnitId]
, componentTargets :: [Target]
, componentFP :: NormalizedFilePath
, _componentCOptions :: ComponentOptions
, componentDependencyInfo :: DependencyInfo
}
checkDependencyInfo :: DependencyInfo -> IO Bool
checkDependencyInfo old_di = do
di <- getDependencyInfo (Map.keys old_di)
return (di == old_di)
getDependencyInfo :: [FilePath] -> IO DependencyInfo
getDependencyInfo fs = Map.fromList <$> mapM do_one fs
where
tryIO :: IO a -> IO (Either IOException a)
tryIO = try
do_one :: FilePath -> IO (FilePath, Maybe UTCTime)
do_one fp = (fp,) . eitherToMaybe <$> tryIO (getModificationTime fp)
removeInplacePackages :: [InstalledUnitId] -> DynFlags -> (DynFlags, [InstalledUnitId])
removeInplacePackages us df = (df { packageFlags = ps
, thisInstalledUnitId = fake_uid }, uids)
where
(uids, ps) = partitionEithers (map go (packageFlags df))
fake_uid = toInstalledUnitId (stringToUnitId "fake_uid")
go p@(ExposePackage _ (UnitIdArg u) _) = if toInstalledUnitId u `elem` us
then Left (toInstalledUnitId u)
else Right p
go p = Right p
memoIO :: Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO op = do
ref <- newVar Map.empty
return $ \k -> join $ mask_ $ modifyVar ref $ \mp ->
case Map.lookup k mp of
Nothing -> do
res <- onceFork $ op k
return (Map.insert k res mp, res)
Just res -> return (mp, res)
setOptions :: GhcMonad m => ComponentOptions -> DynFlags -> m (DynFlags, [Target])
setOptions (ComponentOptions theOpts compRoot _) dflags = do
(dflags', targets) <- addCmdOpts theOpts dflags
let dflags'' =
disableWarningsAsErrors $
flip gopt_unset Opt_WriteInterface $
dontWriteHieFiles $
setIgnoreInterfacePragmas $
setLinkerOptions $
disableOptimisation $
setUpTypedHoles $
makeDynFlagsAbsolute compRoot dflags'
(final_df, _) <- liftIO $ wrapPackageSetupException $ initPackages dflags''
return (final_df, targets)
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions df = df {
ghcLink = LinkInMemory
, hscTarget = HscNothing
, ghcMode = CompManager
}
setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas df =
gopt_set (gopt_set df Opt_IgnoreInterfacePragmas) Opt_IgnoreOptimChanges
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation df = updOptLevel 0 df
setHiDir :: FilePath -> DynFlags -> DynFlags
setHiDir f d =
d { hiDir = Just f}
getCacheDir :: String -> [String] -> IO FilePath
getCacheDir prefix opts = getXdgDirectory XdgCache (cacheDir </> prefix ++ "-" ++ opts_hash)
where
opts_hash = B.unpack $ B16.encode $ H.finalize $ H.updates H.init (map B.pack opts)
cacheDir :: String
cacheDir = "ghcide"
notifyUserImplicitCradle:: FilePath -> FromServerMessage
notifyUserImplicitCradle fp =
NotShowMessage $
NotificationMessage "2.0" WindowShowMessage $ ShowMessageParams MtWarning $
"No [cradle](https://github.com/mpickering/hie-bios#hie-bios) found for "
<> T.pack fp <>
".\n Proceeding with [implicit cradle](https://hackage.haskell.org/package/implicit-hie)"
notifyCradleLoaded :: FilePath -> FromServerMessage
notifyCradleLoaded fp =
NotCustomServer $
NotificationMessage "2.0" (CustomServerMethod cradleLoadedMethod) $
toJSON fp
cradleLoadedMethod :: T.Text
cradleLoadedMethod = "ghcide/cradle/loaded"
data PackageSetupException
= PackageSetupException
{ message :: !String
}
| GhcVersionMismatch
{ compileTime :: !Version
, runTime :: !Version
}
| PackageCheckFailed !NotCompatibleReason
deriving (Eq, Show, Typeable)
instance Exception PackageSetupException
wrapPackageSetupException :: IO a -> IO a
wrapPackageSetupException = handleAny $ \case
e | Just (pkgE :: PackageSetupException) <- fromException e -> throwIO pkgE
e -> (throwIO . PackageSetupException . show) e
showPackageSetupException :: PackageSetupException -> String
showPackageSetupException GhcVersionMismatch{..} = unwords
["ghcide compiled against GHC"
,showVersion compileTime
,"but currently using"
,showVersion runTime
,"\nThis is unsupported, ghcide must be compiled with the same GHC version as the project."
]
showPackageSetupException PackageSetupException{..} = unwords
[ "ghcide compiled by GHC", showVersion compilerVersion
, "failed to load packages:", message <> "."
, "\nPlease ensure that ghcide is compiled with the same GHC installation as the project."]
showPackageSetupException (PackageCheckFailed PackageVersionMismatch{..}) = unwords
["ghcide compiled with package "
, packageName <> "-" <> showVersion compileTime
,"but project uses package"
, packageName <> "-" <> showVersion runTime
,"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project."
]
showPackageSetupException (PackageCheckFailed BasePackageAbiMismatch{..}) = unwords
["ghcide compiled with base-" <> showVersion compileTime <> "-" <> compileTimeAbi
,"but project uses base-" <> showVersion compileTime <> "-" <> runTimeAbi
,"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project."
]
renderPackageSetupException :: FilePath -> PackageSetupException -> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderPackageSetupException fp e =
ideErrorWithSource (Just "cradle") (Just DsError) (toNormalizedFilePath' fp) (T.pack $ showPackageSetupException e)