{-# LANGUAGE CPP          #-}
{-# LANGUAGE TypeFamilies #-}

{-|
The logic for setting up a ghcide session by tapping into hie-bios.
-}
module Development.IDE.Session
  (SessionLoadingOptions(..)
  ,CacheDirs(..)
  ,loadSession
  ,loadSessionWithOptions
  ,setInitialDynFlags
  ,getHieDbLoc
  ,runWithDb
  ) where

-- Unfortunately, we cannot use loadSession with ghc-lib since hie-bios uses
-- the real GHC library and the types are incompatible. Furthermore, when
-- building with ghc-lib we need to make this Haskell agnostic, so no hie-bios!

import           Control.Concurrent.Async
import           Control.Concurrent.Strict
import           Control.Exception.Safe
import           Control.Monad
import           Control.Monad.Extra
import           Control.Monad.IO.Class
import qualified Crypto.Hash.SHA1                     as H
import           Data.Aeson
import           Data.Bifunctor
import qualified Data.ByteString.Base16               as B16
import qualified Data.ByteString.Char8                as B
import           Data.Default
import           Data.Either.Extra
import           Data.Function
import qualified Data.HashMap.Strict                  as HM
import           Data.Hashable
import           Data.IORef
import           Data.List
import qualified Data.Map.Strict                      as Map
import           Data.Maybe
import qualified Data.Text                            as T
import           Data.Time.Clock
import           Data.Version
import           Development.IDE.Core.RuleTypes
import           Development.IDE.Core.Shake
import           Development.IDE.GHC.Compat           hiding (Target,
                                                       TargetFile, TargetModule)
import qualified Development.IDE.GHC.Compat           as GHC
import           Development.IDE.GHC.Util
import           Development.IDE.Graph                (Action)
import           Development.IDE.Session.VersionCheck
import           Development.IDE.Types.Diagnostics
import           Development.IDE.Types.Exports
import           Development.IDE.Types.HscEnvEq       (HscEnvEq, newHscEnvEq,
                                                       newHscEnvEqPreserveImportPaths)
import           Development.IDE.Types.Location
import           Development.IDE.Types.Logger
import           Development.IDE.Types.Options
import           GHC.Check
import qualified HIE.Bios                             as HieBios
import           HIE.Bios.Environment                 hiding (getCacheDir)
import           HIE.Bios.Types
import           Hie.Implicit.Cradle                  (loadImplicitHieCradle)
import           Language.LSP.Server
import           Language.LSP.Types
import           System.Directory
import qualified System.Directory.Extra               as IO
import           System.FilePath
import           System.IO
import           System.Info

import           Control.Applicative                  (Alternative ((<|>)))
import           Control.Exception                    (evaluate)
import           Data.Void
import           GHCi
import           HscTypes                             (hsc_IC, hsc_NC,
                                                       hsc_dflags, ic_dflags)
import           Linker
import           Module
import           NameCache

import           Control.Concurrent.STM               (atomically)
import           Control.Concurrent.STM.TQueue
import qualified Data.HashSet                         as Set
import           Database.SQLite.Simple
import           HieDb.Create
import           HieDb.Types
import           HieDb.Utils
import           Ide.Types                            (dynFlagsModifyGlobal)

-- | Bump this version number when making changes to the format of the data stored in hiedb
hiedbDataVersion :: String
hiedbDataVersion :: String
hiedbDataVersion = String
"1"

data CacheDirs = CacheDirs
  { CacheDirs -> Maybe String
hiCacheDir, CacheDirs -> Maybe String
hieCacheDir, CacheDirs -> Maybe String
oCacheDir :: Maybe FilePath}

data SessionLoadingOptions = SessionLoadingOptions
  { SessionLoadingOptions -> String -> IO (Maybe String)
findCradle             :: FilePath -> IO (Maybe FilePath)
  -- | Load the cradle with an optional 'hie.yaml' location.
  -- If a 'hie.yaml' is given, use it to load the cradle.
  -- Otherwise, use the provided project root directory to determine the cradle type.
  , SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
loadCradle             :: Maybe FilePath -> FilePath -> IO (HieBios.Cradle Void)
  -- | Given the project name and a set of command line flags,
  --   return the path for storing generated GHC artifacts,
  --   or 'Nothing' to respect the cradle setting
  , SessionLoadingOptions -> String -> [String] -> IO CacheDirs
getCacheDirs           :: String -> [String] -> IO CacheDirs
  -- | Return the GHC lib dir to use for the 'unsafeGlobalDynFlags'
  , SessionLoadingOptions -> String -> IO (Maybe LibDir)
getInitialGhcLibDir    :: FilePath -> IO (Maybe LibDir)
  , SessionLoadingOptions -> InstalledUnitId
fakeUid                :: GHC.InstalledUnitId
    -- ^ unit id used to tag the internal component built by ghcide
    --   To reuse external interface files the unit ids must match,
    --   thus make sure to build them with `--this-unit-id` set to the
    --   same value as the ghcide fake uid
  }

instance Default SessionLoadingOptions where
    def :: SessionLoadingOptions
def = SessionLoadingOptions :: (String -> IO (Maybe String))
-> (Maybe String -> String -> IO (Cradle Void))
-> (String -> [String] -> IO CacheDirs)
-> (String -> IO (Maybe LibDir))
-> InstalledUnitId
-> SessionLoadingOptions
SessionLoadingOptions
        {findCradle :: String -> IO (Maybe String)
findCradle = String -> IO (Maybe String)
HieBios.findCradle
        ,loadCradle :: Maybe String -> String -> IO (Cradle Void)
loadCradle = Maybe String -> String -> IO (Cradle Void)
loadWithImplicitCradle
        ,getCacheDirs :: String -> [String] -> IO CacheDirs
getCacheDirs = String -> [String] -> IO CacheDirs
getCacheDirsDefault
        ,getInitialGhcLibDir :: String -> IO (Maybe LibDir)
getInitialGhcLibDir = String -> IO (Maybe LibDir)
getInitialGhcLibDirDefault
        ,fakeUid :: InstalledUnitId
fakeUid = UnitId -> InstalledUnitId
GHC.toInstalledUnitId (String -> UnitId
GHC.stringToUnit String
"main")
        }

-- | Find the cradle for a given 'hie.yaml' configuration.
--
-- If a 'hie.yaml' is given, the cradle is read from the config.
--  If this config does not comply to the "hie.yaml"
-- specification, an error is raised.
--
-- If no location for "hie.yaml" is provided, the implicit config is used
-- using the provided root directory for discovering the project.
-- The implicit config uses different heuristics to determine the type
-- of the project that may or may not be accurate.
loadWithImplicitCradle :: Maybe FilePath
                          -- ^ Optional 'hie.yaml' location. Will be used if given.
                          -> FilePath
                          -- ^ Root directory of the project. Required as a fallback
                          -- if no 'hie.yaml' location is given.
                          -> IO (HieBios.Cradle Void)
loadWithImplicitCradle :: Maybe String -> String -> IO (Cradle Void)
loadWithImplicitCradle Maybe String
mHieYaml String
rootDir = do
  case Maybe String
mHieYaml of
    Just String
yaml -> String -> IO (Cradle Void)
HieBios.loadCradle String
yaml
    Maybe String
Nothing   -> String -> IO (Cradle Void)
forall a. String -> IO (Cradle a)
loadImplicitHieCradle (String -> IO (Cradle Void)) -> String -> IO (Cradle Void)
forall a b. (a -> b) -> a -> b
$ String -> String
addTrailingPathSeparator String
rootDir

getInitialGhcLibDirDefault :: FilePath -> IO (Maybe LibDir)
getInitialGhcLibDirDefault :: String -> IO (Maybe LibDir)
getInitialGhcLibDirDefault String
rootDir = do
  Maybe String
hieYaml <- SessionLoadingOptions -> String -> IO (Maybe String)
findCradle SessionLoadingOptions
forall a. Default a => a
def String
rootDir
  Cradle Void
cradle <- SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
loadCradle SessionLoadingOptions
forall a. Default a => a
def Maybe String
hieYaml String
rootDir
  Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"setInitialDynFlags cradle: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ Cradle Void -> String
forall a. Show a => a -> String
show Cradle Void
cradle
  CradleLoadResult String
libDirRes <- Cradle Void -> IO (CradleLoadResult String)
forall a. Cradle a -> IO (CradleLoadResult String)
getRuntimeGhcLibDir Cradle Void
cradle
  case CradleLoadResult String
libDirRes of
      CradleSuccess String
libdir -> Maybe LibDir -> IO (Maybe LibDir)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe LibDir -> IO (Maybe LibDir))
-> Maybe LibDir -> IO (Maybe LibDir)
forall a b. (a -> b) -> a -> b
$ LibDir -> Maybe LibDir
forall a. a -> Maybe a
Just (LibDir -> Maybe LibDir) -> LibDir -> Maybe LibDir
forall a b. (a -> b) -> a -> b
$ String -> LibDir
LibDir String
libdir
      CradleFail CradleError
err -> do
        Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Couldn't load cradle for libdir: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ (CradleError, String, Maybe String, Cradle Void) -> String
forall a. Show a => a -> String
show (CradleError
err,String
rootDir,Maybe String
hieYaml,Cradle Void
cradle)
        pure Maybe LibDir
forall a. Maybe a
Nothing
      CradleLoadResult String
CradleNone -> do
        Handle -> String -> IO ()
hPutStrLn Handle
stderr String
"Couldn't load cradle (CradleNone)"
        pure Maybe LibDir
forall a. Maybe a
Nothing

-- | Sets `unsafeGlobalDynFlags` on using the hie-bios cradle and returns the GHC libdir
setInitialDynFlags :: FilePath -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags :: String -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags String
rootDir SessionLoadingOptions{InstalledUnitId
String -> IO (Maybe String)
String -> IO (Maybe LibDir)
String -> [String] -> IO CacheDirs
Maybe String -> String -> IO (Cradle Void)
fakeUid :: InstalledUnitId
getInitialGhcLibDir :: String -> IO (Maybe LibDir)
getCacheDirs :: String -> [String] -> IO CacheDirs
loadCradle :: Maybe String -> String -> IO (Cradle Void)
findCradle :: String -> IO (Maybe String)
fakeUid :: SessionLoadingOptions -> InstalledUnitId
getInitialGhcLibDir :: SessionLoadingOptions -> String -> IO (Maybe LibDir)
getCacheDirs :: SessionLoadingOptions -> String -> [String] -> IO CacheDirs
loadCradle :: SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
findCradle :: SessionLoadingOptions -> String -> IO (Maybe String)
..} = do
  Maybe LibDir
libdir <- String -> IO (Maybe LibDir)
getInitialGhcLibDir String
rootDir
  Maybe DynFlags
dynFlags <- (LibDir -> IO DynFlags) -> Maybe LibDir -> IO (Maybe DynFlags)
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM LibDir -> IO DynFlags
dynFlagsForPrinting Maybe LibDir
libdir
  (DynFlags -> IO ()) -> Maybe DynFlags -> IO ()
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DynFlags -> IO ()
setUnsafeGlobalDynFlags Maybe DynFlags
dynFlags
  pure Maybe LibDir
libdir

-- | Wraps `withHieDb` to provide a database connection for reading, and a `HieWriterChan` for
-- writing. Actions are picked off one by one from the `HieWriterChan` and executed in serial
-- by a worker thread using a dedicated database connection.
-- This is done in order to serialize writes to the database, or else SQLite becomes unhappy
runWithDb :: FilePath -> (HieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb :: String -> (HieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb String
fp HieDb -> IndexQueue -> IO ()
k = do
  -- Delete the database if it has an incompatible schema version
  String -> (HieDb -> IO ()) -> IO ()
forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp (IO () -> HieDb -> IO ()
forall a b. a -> b -> a
const (IO () -> HieDb -> IO ()) -> IO () -> HieDb -> IO ()
forall a b. (a -> b) -> a -> b
$ () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ())
    IO () -> (HieDbException -> IO ()) -> IO ()
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \IncompatibleSchemaVersion{} -> String -> IO ()
removeFile String
fp
  String -> (HieDb -> IO ()) -> IO ()
forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp ((HieDb -> IO ()) -> IO ()) -> (HieDb -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \HieDb
writedb -> do
    HieDb -> IO ()
initConn HieDb
writedb
    IndexQueue
chan <- IO IndexQueue
forall a. IO (TQueue a)
newTQueueIO
    IO Any -> (Async Any -> IO ()) -> IO ()
forall a b. IO a -> (Async a -> IO b) -> IO b
withAsync (HieDb -> IndexQueue -> IO Any
forall a. HieDb -> IndexQueue -> IO a
writerThread HieDb
writedb IndexQueue
chan) ((Async Any -> IO ()) -> IO ()) -> (Async Any -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \Async Any
_ -> do
      String -> (HieDb -> IO ()) -> IO ()
forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp ((HieDb -> IndexQueue -> IO ()) -> IndexQueue -> HieDb -> IO ()
forall a b c. (a -> b -> c) -> b -> a -> c
flip HieDb -> IndexQueue -> IO ()
k IndexQueue
chan)
  where
    writerThread :: HieDb -> IndexQueue -> IO a
writerThread HieDb
db IndexQueue
chan = do
      -- Clear the index of any files that might have been deleted since the last run
      HieDb -> IO ()
deleteMissingRealFiles HieDb
db
      Int
_ <- HieDb -> IO Int
garbageCollectTypeNames HieDb
db
      IO () -> IO a
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever (IO () -> IO a) -> IO () -> IO a
forall a b. (a -> b) -> a -> b
$ do
        HieDb -> IO ()
k <- STM (HieDb -> IO ()) -> IO (HieDb -> IO ())
forall a. STM a -> IO a
atomically (STM (HieDb -> IO ()) -> IO (HieDb -> IO ()))
-> STM (HieDb -> IO ()) -> IO (HieDb -> IO ())
forall a b. (a -> b) -> a -> b
$ IndexQueue -> STM (HieDb -> IO ())
forall a. TQueue a -> STM a
readTQueue IndexQueue
chan
        HieDb -> IO ()
k HieDb
db
          IO () -> (SQLError -> IO ()) -> IO ()
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \e :: SQLError
e@SQLError{} -> do
            Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"SQLite error in worker, ignoring: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ SQLError -> String
forall a. Show a => a -> String
show SQLError
e
          IO () -> (SomeException -> IO ()) -> IO ()
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`catchAny` \SomeException
e -> do
            Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Uncaught error in database worker, ignoring: " String -> String -> String
forall a. [a] -> [a] -> [a]
++ SomeException -> String
forall a. Show a => a -> String
show SomeException
e


getHieDbLoc :: FilePath -> IO FilePath
getHieDbLoc :: String -> IO String
getHieDbLoc String
dir = do
  let db :: String
db = String -> [String] -> String
forall a. [a] -> [[a]] -> [a]
intercalate String
"-" [String
dirHash, String -> String
takeBaseName String
dir, VERSION_ghc, hiedbDataVersion] <.> "hiedb"
      dirHash :: String
dirHash = ByteString -> String
B.unpack (ByteString -> String) -> ByteString -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
B16.encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
H.hash (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ String -> ByteString
B.pack String
dir
  String
cDir <- XdgDirectory -> String -> IO String
IO.getXdgDirectory XdgDirectory
IO.XdgCache String
cacheDir
  Bool -> String -> IO ()
createDirectoryIfMissing Bool
True String
cDir
  pure (String
cDir String -> String -> String
</> String
db)

-- | Given a root directory, return a Shake 'Action' which setups an
-- 'IdeGhcSession' given a file.
-- Some of the many things this does:
--
-- * Find the cradle for the file
-- * Get the session options,
-- * Get the GHC lib directory
-- * Make sure the GHC compiletime and runtime versions match
-- * Restart the Shake session
--
-- This is the key function which implements multi-component support. All
-- components mapping to the same hie.yaml file are mapped to the same
-- HscEnv which is updated as new components are discovered.
loadSession :: FilePath -> IO (Action IdeGhcSession)
loadSession :: String -> IO (Action IdeGhcSession)
loadSession = SessionLoadingOptions -> String -> IO (Action IdeGhcSession)
loadSessionWithOptions SessionLoadingOptions
forall a. Default a => a
def

loadSessionWithOptions :: SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions :: SessionLoadingOptions -> String -> IO (Action IdeGhcSession)
loadSessionWithOptions SessionLoadingOptions{InstalledUnitId
String -> IO (Maybe String)
String -> IO (Maybe LibDir)
String -> [String] -> IO CacheDirs
Maybe String -> String -> IO (Cradle Void)
fakeUid :: InstalledUnitId
getInitialGhcLibDir :: String -> IO (Maybe LibDir)
getCacheDirs :: String -> [String] -> IO CacheDirs
loadCradle :: Maybe String -> String -> IO (Cradle Void)
findCradle :: String -> IO (Maybe String)
fakeUid :: SessionLoadingOptions -> InstalledUnitId
getInitialGhcLibDir :: SessionLoadingOptions -> String -> IO (Maybe LibDir)
getCacheDirs :: SessionLoadingOptions -> String -> [String] -> IO CacheDirs
loadCradle :: SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
findCradle :: SessionLoadingOptions -> String -> IO (Maybe String)
..} String
dir = do
  -- Mapping from hie.yaml file to HscEnv, one per hie.yaml file
  Var HieMap
hscEnvs <- HieMap -> IO (Var HieMap)
forall a. a -> IO (Var a)
newVar HieMap
forall k a. Map k a
Map.empty :: IO (Var HieMap)
  -- Mapping from a Filepath to HscEnv
  Var FlagsMap
fileToFlags <- FlagsMap -> IO (Var FlagsMap)
forall a. a -> IO (Var a)
newVar FlagsMap
forall k a. Map k a
Map.empty :: IO (Var FlagsMap)
  -- Mapping from a Filepath to its 'hie.yaml' location.
  -- Should hold the same Filepaths as 'fileToFlags', otherwise
  -- they are inconsistent. So, everywhere you modify 'fileToFlags',
  -- you have to modify 'filesMap' as well.
  Var FilesMap
filesMap <- FilesMap -> IO (Var FilesMap)
forall a. a -> IO (Var a)
newVar FilesMap
forall k v. HashMap k v
HM.empty :: IO (Var FilesMap)
  -- Version of the mappings above
  Var Int
version <- Int -> IO (Var Int)
forall a. a -> IO (Var a)
newVar Int
0
  let returnWithVersion :: (String -> IO (IdeResult HscEnvEq, [String]))
-> Action IdeGhcSession
returnWithVersion String -> IO (IdeResult HscEnvEq, [String])
fun = (String -> IO (IdeResult HscEnvEq, [String]))
-> Int -> IdeGhcSession
IdeGhcSession String -> IO (IdeResult HscEnvEq, [String])
fun (Int -> IdeGhcSession) -> Action Int -> Action IdeGhcSession
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO Int -> Action Int
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (Var Int -> IO Int
forall a. Var a -> IO a
readVar Var Int
version)
  -- This caches the mapping from Mod.hs -> hie.yaml
  String -> IO (Maybe String)
cradleLoc <- IO (String -> IO (Maybe String))
-> IO (String -> IO (Maybe String))
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (String -> IO (Maybe String))
 -> IO (String -> IO (Maybe String)))
-> IO (String -> IO (Maybe String))
-> IO (String -> IO (Maybe String))
forall a b. (a -> b) -> a -> b
$ (String -> IO (Maybe String)) -> IO (String -> IO (Maybe String))
forall a b. Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO ((String -> IO (Maybe String)) -> IO (String -> IO (Maybe String)))
-> (String -> IO (Maybe String))
-> IO (String -> IO (Maybe String))
forall a b. (a -> b) -> a -> b
$ \String
v -> do
      Maybe String
res <- String -> IO (Maybe String)
findCradle String
v
      -- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path
      -- try and normalise that
      -- e.g. see https://github.com/haskell/ghcide/issues/126
      Maybe String
res' <- (String -> IO String) -> Maybe String -> IO (Maybe String)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse String -> IO String
makeAbsolute Maybe String
res
      return $ String -> String
normalise (String -> String) -> Maybe String -> Maybe String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
res'

  Async (IdeResult HscEnvEq, [String])
dummyAs <- IO (IdeResult HscEnvEq, [String])
-> IO (Async (IdeResult HscEnvEq, [String]))
forall a. IO a -> IO (Async a)
async (IO (IdeResult HscEnvEq, [String])
 -> IO (Async (IdeResult HscEnvEq, [String])))
-> IO (IdeResult HscEnvEq, [String])
-> IO (Async (IdeResult HscEnvEq, [String]))
forall a b. (a -> b) -> a -> b
$ (IdeResult HscEnvEq, [String]) -> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. Monad m => a -> m a
return (String -> (IdeResult HscEnvEq, [String])
forall a. HasCallStack => String -> a
error String
"Uninitialised")
  Var (Async (IdeResult HscEnvEq, [String]))
runningCradle <- Async (IdeResult HscEnvEq, [String])
-> IO (Var (Async (IdeResult HscEnvEq, [String])))
forall a. a -> IO (Var a)
newVar Async (IdeResult HscEnvEq, [String])
dummyAs :: IO (Var (Async (IdeResult HscEnvEq,[FilePath])))

  return $ do
    extras :: ShakeExtras
extras@ShakeExtras{Logger
$sel:logger:ShakeExtras :: ShakeExtras -> Logger
logger :: Logger
logger, [DelayedAction ()] -> IO ()
$sel:restartShakeSession:ShakeExtras :: ShakeExtras -> [DelayedAction ()] -> IO ()
restartShakeSession :: [DelayedAction ()] -> IO ()
restartShakeSession, IORef NameCache
$sel:ideNc:ShakeExtras :: ShakeExtras -> IORef NameCache
ideNc :: IORef NameCache
ideNc, Var (Hashed KnownTargets)
$sel:knownTargetsVar:ShakeExtras :: ShakeExtras -> Var (Hashed KnownTargets)
knownTargetsVar :: Var (Hashed KnownTargets)
knownTargetsVar, Maybe (LanguageContextEnv Config)
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv :: Maybe (LanguageContextEnv Config)
lspEnv
                      } <- Action ShakeExtras
getShakeExtras
    let invalidateShakeCache :: IO ()
invalidateShakeCache = do
            IO Int -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO Int -> IO ()) -> IO Int -> IO ()
forall a b. (a -> b) -> a -> b
$ Var Int -> (Int -> Int) -> IO Int
forall a. Var a -> (a -> a) -> IO a
modifyVar' Var Int
version Int -> Int
forall a. Enum a => a -> a
succ
            ShakeExtras -> GhcSessionIO -> [NormalizedFilePath] -> IO ()
forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> IO ()
recordDirtyKeys ShakeExtras
extras GhcSessionIO
GhcSessionIO [NormalizedFilePath
emptyFilePath]

    IdeOptions{ optTesting :: IdeOptions -> IdeTesting
optTesting = IdeTesting Bool
optTesting
              , optCheckProject :: IdeOptions -> IO Bool
optCheckProject = IO Bool
getCheckProject
              , DynFlagsModifications
optModifyDynFlags :: IdeOptions -> DynFlagsModifications
optModifyDynFlags :: DynFlagsModifications
optModifyDynFlags
              , [String]
optExtensions :: IdeOptions -> [String]
optExtensions :: [String]
optExtensions
              } <- Action IdeOptions
getIdeOptions

        -- populate the knownTargetsVar with all the
        -- files in the project so that `knownFiles` can learn about them and
        -- we can generate a complete module graph
    let extendKnownTargets :: [TargetDetails] -> IO (Hashed KnownTargets)
extendKnownTargets [TargetDetails]
newTargets = do
          [(Target, [NormalizedFilePath])]
knownTargets <- [TargetDetails]
-> (TargetDetails -> IO (Target, [NormalizedFilePath]))
-> IO [(Target, [NormalizedFilePath])]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [TargetDetails]
newTargets ((TargetDetails -> IO (Target, [NormalizedFilePath]))
 -> IO [(Target, [NormalizedFilePath])])
-> (TargetDetails -> IO (Target, [NormalizedFilePath]))
-> IO [(Target, [NormalizedFilePath])]
forall a b. (a -> b) -> a -> b
$ \TargetDetails{[NormalizedFilePath]
IdeResult HscEnvEq
DependencyInfo
Target
targetLocations :: TargetDetails -> [NormalizedFilePath]
targetDepends :: TargetDetails -> DependencyInfo
targetEnv :: TargetDetails -> IdeResult HscEnvEq
targetTarget :: TargetDetails -> Target
targetLocations :: [NormalizedFilePath]
targetDepends :: DependencyInfo
targetEnv :: IdeResult HscEnvEq
targetTarget :: Target
..} ->
            case Target
targetTarget of
              TargetFile NormalizedFilePath
f -> (Target, [NormalizedFilePath]) -> IO (Target, [NormalizedFilePath])
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target
targetTarget, [NormalizedFilePath
f])
              TargetModule ModuleName
_ -> do
                [NormalizedFilePath]
found <- (NormalizedFilePath -> IO Bool)
-> [NormalizedFilePath] -> IO [NormalizedFilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesFileExist (String -> IO Bool)
-> (NormalizedFilePath -> String) -> NormalizedFilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath -> String
fromNormalizedFilePath) [NormalizedFilePath]
targetLocations
                return (Target
targetTarget, [NormalizedFilePath]
found)
          Var (Hashed KnownTargets)
-> (Hashed KnownTargets -> IO (Hashed KnownTargets))
-> IO (Hashed KnownTargets)
forall a. Var a -> (a -> IO a) -> IO a
modifyVarIO' Var (Hashed KnownTargets)
knownTargetsVar ((Hashed KnownTargets -> IO (Hashed KnownTargets))
 -> IO (Hashed KnownTargets))
-> (Hashed KnownTargets -> IO (Hashed KnownTargets))
-> IO (Hashed KnownTargets)
forall a b. (a -> b) -> a -> b
$ (KnownTargets -> IO KnownTargets)
-> Hashed KnownTargets -> IO (Hashed KnownTargets)
forall b (f :: * -> *) a.
(Hashable b, Functor f) =>
(a -> f b) -> Hashed a -> f (Hashed b)
traverseHashed ((KnownTargets -> IO KnownTargets)
 -> Hashed KnownTargets -> IO (Hashed KnownTargets))
-> (KnownTargets -> IO KnownTargets)
-> Hashed KnownTargets
-> IO (Hashed KnownTargets)
forall a b. (a -> b) -> a -> b
$ \KnownTargets
known -> do
            let known' :: KnownTargets
known' = (HashSet NormalizedFilePath
 -> HashSet NormalizedFilePath -> HashSet NormalizedFilePath)
-> KnownTargets -> KnownTargets -> KnownTargets
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith HashSet NormalizedFilePath
-> HashSet NormalizedFilePath -> HashSet NormalizedFilePath
forall a. Semigroup a => a -> a -> a
(<>) KnownTargets
known (KnownTargets -> KnownTargets) -> KnownTargets -> KnownTargets
forall a b. (a -> b) -> a -> b
$ [(Target, HashSet NormalizedFilePath)] -> KnownTargets
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([(Target, HashSet NormalizedFilePath)] -> KnownTargets)
-> [(Target, HashSet NormalizedFilePath)] -> KnownTargets
forall a b. (a -> b) -> a -> b
$ ((Target, [NormalizedFilePath])
 -> (Target, HashSet NormalizedFilePath))
-> [(Target, [NormalizedFilePath])]
-> [(Target, HashSet NormalizedFilePath)]
forall a b. (a -> b) -> [a] -> [b]
map (([NormalizedFilePath] -> HashSet NormalizedFilePath)
-> (Target, [NormalizedFilePath])
-> (Target, HashSet NormalizedFilePath)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second [NormalizedFilePath] -> HashSet NormalizedFilePath
forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList) [(Target, [NormalizedFilePath])]
knownTargets
            Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (KnownTargets
known KnownTargets -> KnownTargets -> Bool
forall a. Eq a => a -> a -> Bool
/= KnownTargets
known') (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
                Logger -> Text -> IO ()
logDebug Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"Known files updated: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
                    String -> Text
T.pack(HashMap Target (HashSet String) -> String
forall a. Show a => a -> String
show (HashMap Target (HashSet String) -> String)
-> HashMap Target (HashSet String) -> String
forall a b. (a -> b) -> a -> b
$ ((HashSet NormalizedFilePath -> HashSet String)
-> KnownTargets -> HashMap Target (HashSet String)
forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map ((HashSet NormalizedFilePath -> HashSet String)
 -> KnownTargets -> HashMap Target (HashSet String))
-> ((NormalizedFilePath -> String)
    -> HashSet NormalizedFilePath -> HashSet String)
-> (NormalizedFilePath -> String)
-> KnownTargets
-> HashMap Target (HashSet String)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (NormalizedFilePath -> String)
-> HashSet NormalizedFilePath -> HashSet String
forall b a.
(Hashable b, Eq b) =>
(a -> b) -> HashSet a -> HashSet b
Set.map) NormalizedFilePath -> String
fromNormalizedFilePath KnownTargets
known')
            pure KnownTargets
known'

    -- Create a new HscEnv from a hieYaml root and a set of options
    -- If the hieYaml file already has an HscEnv, the new component is
    -- combined with the components in the old HscEnv into a new HscEnv
    -- which contains the union.
    let packageSetup :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
                     -> IO (HscEnv, ComponentInfo, [ComponentInfo])
        packageSetup :: (Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
packageSetup (Maybe String
hieYaml, NormalizedFilePath
cfp, ComponentOptions
opts, String
libDir) = do
          -- Parse DynFlags for the newly discovered component
          HscEnv
hscEnv <- IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
ideNc String
libDir
          (DynFlags
df, [Target]
targets) <- HscEnv -> Ghc (DynFlags, [Target]) -> IO (DynFlags, [Target])
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hscEnv (Ghc (DynFlags, [Target]) -> IO (DynFlags, [Target]))
-> Ghc (DynFlags, [Target]) -> IO (DynFlags, [Target])
forall a b. (a -> b) -> a -> b
$
              (DynFlags -> DynFlags)
-> (DynFlags, [Target]) -> (DynFlags, [Target])
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (DynFlagsModifications -> DynFlags -> DynFlags
dynFlagsModifyGlobal DynFlagsModifications
optModifyDynFlags) ((DynFlags, [Target]) -> (DynFlags, [Target]))
-> Ghc (DynFlags, [Target]) -> Ghc (DynFlags, [Target])
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ComponentOptions -> DynFlags -> Ghc (DynFlags, [Target])
forall (m :: * -> *).
GhcMonad m =>
ComponentOptions -> DynFlags -> m (DynFlags, [Target])
setOptions ComponentOptions
opts (HscEnv -> DynFlags
hsc_dflags HscEnv
hscEnv)
          let deps :: [String]
deps = ComponentOptions -> [String]
componentDependencies ComponentOptions
opts [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
hieYaml
          DependencyInfo
dep_info <- [String] -> IO DependencyInfo
getDependencyInfo [String]
deps
          -- Now lookup to see whether we are combining with an existing HscEnv
          -- or making a new one. The lookup returns the HscEnv and a list of
          -- information about other components loaded into the HscEnv
          -- (unitId, DynFlag, Targets)
          Var HieMap
-> (HieMap
    -> IO (HieMap, (HscEnv, ComponentInfo, [ComponentInfo])))
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var HieMap
hscEnvs ((HieMap -> IO (HieMap, (HscEnv, ComponentInfo, [ComponentInfo])))
 -> IO (HscEnv, ComponentInfo, [ComponentInfo]))
-> (HieMap
    -> IO (HieMap, (HscEnv, ComponentInfo, [ComponentInfo])))
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
forall a b. (a -> b) -> a -> b
$ \HieMap
m -> do
              -- Just deps if there's already an HscEnv
              -- Nothing is it's the first time we are making an HscEnv
              let oldDeps :: Maybe (HscEnv, [RawComponentInfo])
oldDeps = Maybe String -> HieMap -> Maybe (HscEnv, [RawComponentInfo])
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Maybe String
hieYaml HieMap
m
              let -- Add the raw information about this component to the list
                  -- We will modify the unitId and DynFlags used for
                  -- compilation but these are the true source of
                  -- information.
                  new_deps :: [RawComponentInfo]
new_deps = InstalledUnitId
-> DynFlags
-> [Target]
-> NormalizedFilePath
-> ComponentOptions
-> DependencyInfo
-> RawComponentInfo
RawComponentInfo (DynFlags -> InstalledUnitId
thisInstalledUnitId DynFlags
df) DynFlags
df [Target]
targets NormalizedFilePath
cfp ComponentOptions
opts DependencyInfo
dep_info
                                RawComponentInfo -> [RawComponentInfo] -> [RawComponentInfo]
forall a. a -> [a] -> [a]
: [RawComponentInfo]
-> ((HscEnv, [RawComponentInfo]) -> [RawComponentInfo])
-> Maybe (HscEnv, [RawComponentInfo])
-> [RawComponentInfo]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] (HscEnv, [RawComponentInfo]) -> [RawComponentInfo]
forall a b. (a, b) -> b
snd Maybe (HscEnv, [RawComponentInfo])
oldDeps
                  -- Get all the unit-ids for things in this component
                  inplace :: [InstalledUnitId]
inplace = (RawComponentInfo -> InstalledUnitId)
-> [RawComponentInfo] -> [InstalledUnitId]
forall a b. (a -> b) -> [a] -> [b]
map RawComponentInfo -> InstalledUnitId
rawComponentUnitId [RawComponentInfo]
new_deps

              [ComponentInfo]
new_deps' <- [RawComponentInfo]
-> (RawComponentInfo -> IO ComponentInfo) -> IO [ComponentInfo]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [RawComponentInfo]
new_deps ((RawComponentInfo -> IO ComponentInfo) -> IO [ComponentInfo])
-> (RawComponentInfo -> IO ComponentInfo) -> IO [ComponentInfo]
forall a b. (a -> b) -> a -> b
$ \RawComponentInfo{[Target]
DependencyInfo
InstalledUnitId
DynFlags
ComponentOptions
NormalizedFilePath
rawComponentDependencyInfo :: RawComponentInfo -> DependencyInfo
rawComponentCOptions :: RawComponentInfo -> ComponentOptions
rawComponentFP :: RawComponentInfo -> NormalizedFilePath
rawComponentTargets :: RawComponentInfo -> [Target]
rawComponentDynFlags :: RawComponentInfo -> DynFlags
rawComponentDependencyInfo :: DependencyInfo
rawComponentCOptions :: ComponentOptions
rawComponentFP :: NormalizedFilePath
rawComponentTargets :: [Target]
rawComponentDynFlags :: DynFlags
rawComponentUnitId :: InstalledUnitId
rawComponentUnitId :: RawComponentInfo -> InstalledUnitId
..} -> do
                  -- Remove all inplace dependencies from package flags for
                  -- components in this HscEnv
                  let (DynFlags
df2, [InstalledUnitId]
uids) = InstalledUnitId
-> [InstalledUnitId] -> DynFlags -> (DynFlags, [InstalledUnitId])
removeInplacePackages InstalledUnitId
fakeUid [InstalledUnitId]
inplace DynFlags
rawComponentDynFlags
                  let prefix :: String
prefix = InstalledUnitId -> String
forall a. Show a => a -> String
show InstalledUnitId
rawComponentUnitId
                  -- See Note [Avoiding bad interface files]
                  let hscComponents :: [String]
hscComponents = [String] -> [String]
forall a. Ord a => [a] -> [a]
sort ([String] -> [String]) -> [String] -> [String]
forall a b. (a -> b) -> a -> b
$ (InstalledUnitId -> String) -> [InstalledUnitId] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map InstalledUnitId -> String
forall a. Show a => a -> String
show [InstalledUnitId]
uids
                      cacheDirOpts :: [String]
cacheDirOpts = [String]
hscComponents [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ ComponentOptions -> [String]
componentOptions ComponentOptions
opts
                  CacheDirs
cacheDirs <- IO CacheDirs -> IO CacheDirs
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO CacheDirs -> IO CacheDirs) -> IO CacheDirs -> IO CacheDirs
forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO CacheDirs
getCacheDirs String
prefix [String]
cacheDirOpts
                  DynFlags
processed_df <- Logger -> CacheDirs -> DynFlags -> IO DynFlags
forall (m :: * -> *).
MonadIO m =>
Logger -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs Logger
logger CacheDirs
cacheDirs DynFlags
df2
                  -- The final component information, mostly the same but the DynFlags don't
                  -- contain any packages which are also loaded
                  -- into the same component.
                  pure $ InstalledUnitId
-> DynFlags
-> [InstalledUnitId]
-> [Target]
-> NormalizedFilePath
-> ComponentOptions
-> DependencyInfo
-> ComponentInfo
ComponentInfo InstalledUnitId
rawComponentUnitId
                                       DynFlags
processed_df
                                       [InstalledUnitId]
uids
                                       [Target]
rawComponentTargets
                                       NormalizedFilePath
rawComponentFP
                                       ComponentOptions
rawComponentCOptions
                                       DependencyInfo
rawComponentDependencyInfo
              -- Make a new HscEnv, we have to recompile everything from
              -- scratch again (for now)
              -- It's important to keep the same NameCache though for reasons
              -- that I do not fully understand
              Logger -> Text -> IO ()
logInfo Logger
logger (String -> Text
T.pack (String
"Making new HscEnv" String -> String -> String
forall a. [a] -> [a] -> [a]
++ [InstalledUnitId] -> String
forall a. Show a => a -> String
show [InstalledUnitId]
inplace))
              HscEnv
hscEnv <- IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
ideNc String
libDir
              HscEnv
newHscEnv <-
                -- Add the options for the current component to the HscEnv
                HscEnv -> Ghc HscEnv -> IO HscEnv
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hscEnv (Ghc HscEnv -> IO HscEnv) -> Ghc HscEnv -> IO HscEnv
forall a b. (a -> b) -> a -> b
$ do
                  [InstalledUnitId]
_ <- DynFlags -> Ghc [InstalledUnitId]
forall (m :: * -> *). GhcMonad m => DynFlags -> m [InstalledUnitId]
setSessionDynFlags DynFlags
df
                  Ghc HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession

              -- Modify the map so the hieYaml now maps to the newly created
              -- HscEnv
              -- Returns
              -- . the new HscEnv so it can be used to modify the
              --   FilePath -> HscEnv map (fileToFlags)
              -- . The information for the new component which caused this cache miss
              -- . The modified information (without -inplace flags) for
              --   existing packages
              pure (Maybe String -> (HscEnv, [RawComponentInfo]) -> HieMap -> HieMap
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Maybe String
hieYaml (HscEnv
newHscEnv, [RawComponentInfo]
new_deps) HieMap
m, (HscEnv
newHscEnv, [ComponentInfo] -> ComponentInfo
forall a. [a] -> a
head [ComponentInfo]
new_deps', [ComponentInfo] -> [ComponentInfo]
forall a. [a] -> [a]
tail [ComponentInfo]
new_deps'))


    let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
                -> IO (IdeResult HscEnvEq,[FilePath])
        session :: (Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (IdeResult HscEnvEq, [String])
session args :: (Maybe String, NormalizedFilePath, ComponentOptions, String)
args@(Maybe String
hieYaml, NormalizedFilePath
_cfp, ComponentOptions
_opts, String
_libDir) = do
          (HscEnv
hscEnv, ComponentInfo
new, [ComponentInfo]
old_deps) <- (Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (HscEnv, ComponentInfo, [ComponentInfo])
packageSetup (Maybe String, NormalizedFilePath, ComponentOptions, String)
args

          -- Whenever we spin up a session on Linux, dynamically load libm.so.6
          -- in. We need this in case the binary is statically linked, in which
          -- case the interactive session will fail when trying to load
          -- ghc-prim, which happens whenever Template Haskell is being
          -- evaluated or haskell-language-server's eval plugin tries to run
          -- some code. If the binary is dynamically linked, then this will have
          -- no effect.
          -- See https://github.com/haskell/haskell-language-server/issues/221
          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
os String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
"linux") (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
            HscEnv -> IO ()
initObjLinker HscEnv
hscEnv
            Maybe String
res <- HscEnv -> String -> IO (Maybe String)
loadDLL HscEnv
hscEnv String
"libm.so.6"
            case Maybe String
res of
              Maybe String
Nothing -> () -> IO ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
              Just String
err -> Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$
                String
"Error dynamically loading libm.so.6:\n" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
err

          -- Make a map from unit-id to DynFlags, this is used when trying to
          -- resolve imports. (especially PackageImports)
          let uids :: [(InstalledUnitId, DynFlags)]
uids = (ComponentInfo -> (InstalledUnitId, DynFlags))
-> [ComponentInfo] -> [(InstalledUnitId, DynFlags)]
forall a b. (a -> b) -> [a] -> [b]
map (\ComponentInfo
ci -> (ComponentInfo -> InstalledUnitId
componentUnitId ComponentInfo
ci, ComponentInfo -> DynFlags
componentDynFlags ComponentInfo
ci)) (ComponentInfo
new ComponentInfo -> [ComponentInfo] -> [ComponentInfo]
forall a. a -> [a] -> [a]
: [ComponentInfo]
old_deps)

          -- For each component, now make a new HscEnvEq which contains the
          -- HscEnv for the hie.yaml file but the DynFlags for that component

          -- New HscEnv for the component in question, returns the new HscEnvEq and
          -- a mapping from FilePath to the newly created HscEnvEq.
          let new_cache :: ComponentInfo
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
new_cache = Logger
-> [String]
-> Maybe String
-> NormalizedFilePath
-> HscEnv
-> [(InstalledUnitId, DynFlags)]
-> ComponentInfo
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
newComponentCache Logger
logger [String]
optExtensions Maybe String
hieYaml NormalizedFilePath
_cfp HscEnv
hscEnv [(InstalledUnitId, DynFlags)]
uids
          ([TargetDetails]
cs, (IdeResult HscEnvEq, DependencyInfo)
res) <- ComponentInfo
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
new_cache ComponentInfo
new
          -- Modified cache targets for everything else in the hie.yaml file
          -- which now uses the same EPS and so on
          [TargetDetails]
cached_targets <- (ComponentInfo -> IO [TargetDetails])
-> [ComponentInfo] -> IO [TargetDetails]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM ((([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
 -> [TargetDetails])
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
-> IO [TargetDetails]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
-> [TargetDetails]
forall a b. (a, b) -> a
fst (IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
 -> IO [TargetDetails])
-> (ComponentInfo
    -> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo)))
-> ComponentInfo
-> IO [TargetDetails]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComponentInfo
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
new_cache) [ComponentInfo]
old_deps

          let all_targets :: [TargetDetails]
all_targets = [TargetDetails]
cs [TargetDetails] -> [TargetDetails] -> [TargetDetails]
forall a. [a] -> [a] -> [a]
++ [TargetDetails]
cached_targets

          IO FlagsMap -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO FlagsMap -> IO ()) -> IO FlagsMap -> IO ()
forall a b. (a -> b) -> a -> b
$ Var FlagsMap -> (FlagsMap -> FlagsMap) -> IO FlagsMap
forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FlagsMap
fileToFlags ((FlagsMap -> FlagsMap) -> IO FlagsMap)
-> (FlagsMap -> FlagsMap) -> IO FlagsMap
forall a b. (a -> b) -> a -> b
$
              Maybe String
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> FlagsMap
-> FlagsMap
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Maybe String
hieYaml ([(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ((TargetDetails
 -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))])
-> [TargetDetails]
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap [TargetDetails]
all_targets))
          IO FilesMap -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO FilesMap -> IO ()) -> IO FilesMap -> IO ()
forall a b. (a -> b) -> a -> b
$ Var FilesMap -> (FilesMap -> FilesMap) -> IO FilesMap
forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FilesMap
filesMap ((FilesMap -> FilesMap) -> IO FilesMap)
-> (FilesMap -> FilesMap) -> IO FilesMap
forall a b. (a -> b) -> a -> b
$
              (FilesMap -> FilesMap -> FilesMap)
-> FilesMap -> FilesMap -> FilesMap
forall a b c. (a -> b -> c) -> b -> a -> c
flip FilesMap -> FilesMap -> FilesMap
forall k v.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k v -> HashMap k v
HM.union ([(NormalizedFilePath, Maybe String)] -> FilesMap
forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList ([NormalizedFilePath]
-> [Maybe String] -> [(NormalizedFilePath, Maybe String)]
forall a b. [a] -> [b] -> [(a, b)]
zip (((NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))
 -> NormalizedFilePath)
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
-> [NormalizedFilePath]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))
-> NormalizedFilePath
forall a b. (a, b) -> a
fst ([(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
 -> [NormalizedFilePath])
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
-> [NormalizedFilePath]
forall a b. (a -> b) -> a -> b
$ (TargetDetails
 -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))])
-> [TargetDetails]
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap [TargetDetails]
all_targets) (Maybe String -> [Maybe String]
forall a. a -> [a]
repeat Maybe String
hieYaml)))

          IO (Hashed KnownTargets) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (Hashed KnownTargets) -> IO ())
-> IO (Hashed KnownTargets) -> IO ()
forall a b. (a -> b) -> a -> b
$ [TargetDetails] -> IO (Hashed KnownTargets)
extendKnownTargets [TargetDetails]
all_targets

          -- Invalidate all the existing GhcSession build nodes by restarting the Shake session
          IO ()
invalidateShakeCache
          [DelayedAction ()] -> IO ()
restartShakeSession []

          -- Typecheck all files in the project on startup
          Bool
checkProject <- IO Bool
getCheckProject
          Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless ([TargetDetails] -> Bool
forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TargetDetails]
cs Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
checkProject) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ do
                [NormalizedFilePath]
cfps' <- IO [NormalizedFilePath] -> IO [NormalizedFilePath]
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO [NormalizedFilePath] -> IO [NormalizedFilePath])
-> IO [NormalizedFilePath] -> IO [NormalizedFilePath]
forall a b. (a -> b) -> a -> b
$ (NormalizedFilePath -> IO Bool)
-> [NormalizedFilePath] -> IO [NormalizedFilePath]
forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesFileExist (String -> IO Bool)
-> (NormalizedFilePath -> String) -> NormalizedFilePath -> IO Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath -> String
fromNormalizedFilePath) ((TargetDetails -> [NormalizedFilePath])
-> [TargetDetails] -> [NormalizedFilePath]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails -> [NormalizedFilePath]
targetLocations [TargetDetails]
cs)
                IO (IO ()) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (IO ()) -> IO ()) -> IO (IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ ShakeExtras -> DelayedAction () -> IO (IO ())
forall a. ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue ShakeExtras
extras (DelayedAction () -> IO (IO ())) -> DelayedAction () -> IO (IO ())
forall a b. (a -> b) -> a -> b
$ String -> Priority -> Action () -> DelayedAction ()
forall a. String -> Priority -> Action a -> DelayedAction a
mkDelayedAction String
"InitialLoad" Priority
Debug (Action () -> DelayedAction ()) -> Action () -> DelayedAction ()
forall a b. (a -> b) -> a -> b
$ Action () -> Action ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (Action () -> Action ()) -> Action () -> Action ()
forall a b. (a -> b) -> a -> b
$ do
                    [Maybe FileVersion]
mmt <- GetModificationTime
-> [NormalizedFilePath] -> Action [Maybe FileVersion]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses GetModificationTime
GetModificationTime [NormalizedFilePath]
cfps'
                    let cs_exist :: [NormalizedFilePath]
cs_exist = [Maybe NormalizedFilePath] -> [NormalizedFilePath]
forall a. [Maybe a] -> [a]
catMaybes ((NormalizedFilePath
 -> Maybe FileVersion -> Maybe NormalizedFilePath)
-> [NormalizedFilePath]
-> [Maybe FileVersion]
-> [Maybe NormalizedFilePath]
forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith NormalizedFilePath -> Maybe FileVersion -> Maybe NormalizedFilePath
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
(<$) [NormalizedFilePath]
cfps' [Maybe FileVersion]
mmt)
                    [Maybe HiFileResult]
modIfaces <- GetModIface -> [NormalizedFilePath] -> Action [Maybe HiFileResult]
forall k v.
IdeRule k v =>
k -> [NormalizedFilePath] -> Action [Maybe v]
uses GetModIface
GetModIface [NormalizedFilePath]
cs_exist
                    -- update exports map
                    ShakeExtras
extras <- Action ShakeExtras
getShakeExtras
                    let !exportsMap' :: ExportsMap
exportsMap' = [ModIface] -> ExportsMap
createExportsMap ([ModIface] -> ExportsMap) -> [ModIface] -> ExportsMap
forall a b. (a -> b) -> a -> b
$ (Maybe HiFileResult -> Maybe ModIface)
-> [Maybe HiFileResult] -> [ModIface]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe ((HiFileResult -> ModIface) -> Maybe HiFileResult -> Maybe ModIface
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HiFileResult -> ModIface
hirModIface) [Maybe HiFileResult]
modIfaces
                    IO () -> Action ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> Action ()) -> IO () -> Action ()
forall a b. (a -> b) -> a -> b
$ Var ExportsMap -> (ExportsMap -> IO ExportsMap) -> IO ()
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ (ShakeExtras -> Var ExportsMap
exportsMap ShakeExtras
extras) ((ExportsMap -> IO ExportsMap) -> IO ())
-> (ExportsMap -> IO ExportsMap) -> IO ()
forall a b. (a -> b) -> a -> b
$ ExportsMap -> IO ExportsMap
forall a. a -> IO a
evaluate (ExportsMap -> IO ExportsMap)
-> (ExportsMap -> ExportsMap) -> ExportsMap -> IO ExportsMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (ExportsMap
exportsMap' ExportsMap -> ExportsMap -> ExportsMap
forall a. Semigroup a => a -> a -> a
<>)

          return ((DependencyInfo -> [String])
-> (IdeResult HscEnvEq, DependencyInfo)
-> (IdeResult HscEnvEq, [String])
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second DependencyInfo -> [String]
forall k a. Map k a -> [k]
Map.keys (IdeResult HscEnvEq, DependencyInfo)
res)

    let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq, [FilePath])
        consultCradle :: Maybe String -> String -> IO (IdeResult HscEnvEq, [String])
consultCradle Maybe String
hieYaml String
cfp = do
           String
lfp <- (String -> String -> String) -> String -> String -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> String
makeRelative String
cfp (String -> String) -> IO String -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getCurrentDirectory
           Logger -> Text -> IO ()
logInfo Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String
"Consulting the cradle for " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String -> String
forall a. Show a => a -> String
show String
lfp)

           Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (Maybe String -> Bool
forall a. Maybe a -> Bool
isNothing Maybe String
hieYaml) (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
             Logger -> Text -> IO ()
logWarning Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
implicitCradleWarning String
lfp

           Cradle Void
cradle <- Maybe String -> String -> IO (Cradle Void)
loadCradle Maybe String
hieYaml String
dir
           String
lfp <- (String -> String -> String) -> String -> String -> String
forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> String -> String
makeRelative String
cfp (String -> String) -> IO String -> IO String
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getCurrentDirectory

           Bool -> IO () -> IO ()
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
optTesting (IO () -> IO ()) -> IO () -> IO ()
forall a b. (a -> b) -> a -> b
$ Maybe (LanguageContextEnv Config) -> LspT Config IO () -> IO ()
forall (m :: * -> *) c.
Applicative m =>
Maybe (LanguageContextEnv c) -> LspT c m () -> m ()
mRunLspT Maybe (LanguageContextEnv Config)
lspEnv (LspT Config IO () -> IO ()) -> LspT Config IO () -> IO ()
forall a b. (a -> b) -> a -> b
$
            SServerMethod 'CustomMethod
-> MessageParams 'CustomMethod -> LspT Config IO ()
forall (m :: Method 'FromServer 'Notification) (f :: * -> *)
       config.
MonadLsp config f =>
SServerMethod m -> MessageParams m -> f ()
sendNotification (Text -> SServerMethod 'CustomMethod
forall (f :: From) (t :: MethodType). Text -> SMethod 'CustomMethod
SCustomMethod Text
"ghcide/cradle/loaded") (String -> Value
forall a. ToJSON a => a -> Value
toJSON String
cfp)

           -- Display a user friendly progress message here: They probably don't know what a cradle is
           let progMsg :: Text
progMsg = Text
"Setting up " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> String
takeBaseName (Cradle Void -> String
forall a. Cradle a -> String
cradleRootDir Cradle Void
cradle))
                         Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
" (for " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
lfp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
           Either [CradleError] (ComponentOptions, String)
eopts <- Maybe (LanguageContextEnv Config)
-> (LspT
      Config IO (Either [CradleError] (ComponentOptions, String))
    -> LspT
         Config IO (Either [CradleError] (ComponentOptions, String)))
-> IO (Either [CradleError] (ComponentOptions, String))
-> IO (Either [CradleError] (ComponentOptions, String))
forall (m :: * -> *) c a.
Monad m =>
Maybe (LanguageContextEnv c)
-> (LspT c m a -> LspT c m a) -> m a -> m a
mRunLspTCallback Maybe (LanguageContextEnv Config)
lspEnv (Text
-> ProgressCancellable
-> LspT Config IO (Either [CradleError] (ComponentOptions, String))
-> LspT Config IO (Either [CradleError] (ComponentOptions, String))
forall c (m :: * -> *) a.
MonadLsp c m =>
Text -> ProgressCancellable -> m a -> m a
withIndefiniteProgress Text
progMsg ProgressCancellable
NotCancellable) (IO (Either [CradleError] (ComponentOptions, String))
 -> IO (Either [CradleError] (ComponentOptions, String)))
-> IO (Either [CradleError] (ComponentOptions, String))
-> IO (Either [CradleError] (ComponentOptions, String))
forall a b. (a -> b) -> a -> b
$
              Cradle Void
-> String -> IO (Either [CradleError] (ComponentOptions, String))
forall a.
Show a =>
Cradle a
-> String -> IO (Either [CradleError] (ComponentOptions, String))
cradleToOptsAndLibDir Cradle Void
cradle String
cfp

           Logger -> Text -> IO ()
logDebug Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ String -> Text
T.pack (String
"Session loading result: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Either [CradleError] (ComponentOptions, String) -> String
forall a. Show a => a -> String
show Either [CradleError] (ComponentOptions, String)
eopts)
           case Either [CradleError] (ComponentOptions, String)
eopts of
             -- The cradle gave us some options so get to work turning them
             -- into and HscEnv.
             Right (ComponentOptions
opts, String
libDir) -> do
               InstallationCheck
installationCheck <- GhcVersionChecker
ghcVersionChecker String
libDir
               case InstallationCheck
installationCheck of
                 InstallationNotFound{String
$sel:libdir:InstallationChecked :: InstallationCheck -> String
libdir :: String
..} ->
                     String -> IO (IdeResult HscEnvEq, [String])
forall a. HasCallStack => String -> a
error (String -> IO (IdeResult HscEnvEq, [String]))
-> String -> IO (IdeResult HscEnvEq, [String])
forall a b. (a -> b) -> a -> b
$ String
"GHC installation not found in libdir: " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
libdir
                 InstallationMismatch{String
Version
$sel:compileTime:InstallationChecked :: InstallationCheck -> Version
$sel:runTime:InstallationChecked :: InstallationCheck -> Version
runTime :: Version
compileTime :: Version
libdir :: String
$sel:libdir:InstallationChecked :: InstallationCheck -> String
..} ->
                     (IdeResult HscEnvEq, [String]) -> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. Monad m => a -> m a
return (([String
-> PackageSetupException
-> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderPackageSetupException String
cfp GhcVersionMismatch :: Version -> Version -> PackageSetupException
GhcVersionMismatch{Version
runTime :: Version
compileTime :: Version
runTime :: Version
compileTime :: Version
..}], Maybe HscEnvEq
forall a. Maybe a
Nothing),[])
                 InstallationChecked Version
_compileTime Ghc PackageCheckResult
_ghcLibCheck ->
                   (Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (IdeResult HscEnvEq, [String])
session (Maybe String
hieYaml, String -> NormalizedFilePath
toNormalizedFilePath' String
cfp, ComponentOptions
opts, String
libDir)
             -- Failure case, either a cradle error or the none cradle
             Left [CradleError]
err -> do
               DependencyInfo
dep_info <- [String] -> IO DependencyInfo
getDependencyInfo (Maybe String -> [String]
forall a. Maybe a -> [a]
maybeToList Maybe String
hieYaml)
               let ncfp :: NormalizedFilePath
ncfp = String -> NormalizedFilePath
toNormalizedFilePath' String
cfp
               let res :: IdeResult HscEnvEq
res = ((CradleError -> (NormalizedFilePath, ShowDiagnostic, Diagnostic))
-> [CradleError]
-> [(NormalizedFilePath, ShowDiagnostic, Diagnostic)]
forall a b. (a -> b) -> [a] -> [b]
map (NormalizedFilePath
-> CradleError -> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderCradleError NormalizedFilePath
ncfp) [CradleError]
err, Maybe HscEnvEq
forall a. Maybe a
Nothing)
               IO FlagsMap -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO FlagsMap -> IO ()) -> IO FlagsMap -> IO ()
forall a b. (a -> b) -> a -> b
$ Var FlagsMap -> (FlagsMap -> FlagsMap) -> IO FlagsMap
forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FlagsMap
fileToFlags ((FlagsMap -> FlagsMap) -> IO FlagsMap)
-> (FlagsMap -> FlagsMap) -> IO FlagsMap
forall a b. (a -> b) -> a -> b
$
                    (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
 -> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
 -> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
-> Maybe String
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> FlagsMap
-> FlagsMap
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall k v.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k v -> HashMap k v
HM.union Maybe String
hieYaml (NormalizedFilePath
-> (IdeResult HscEnvEq, DependencyInfo)
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton NormalizedFilePath
ncfp (IdeResult HscEnvEq
res, DependencyInfo
dep_info))
               IO FilesMap -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO FilesMap -> IO ()) -> IO FilesMap -> IO ()
forall a b. (a -> b) -> a -> b
$ Var FilesMap -> (FilesMap -> FilesMap) -> IO FilesMap
forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FilesMap
filesMap ((FilesMap -> FilesMap) -> IO FilesMap)
-> (FilesMap -> FilesMap) -> IO FilesMap
forall a b. (a -> b) -> a -> b
$ NormalizedFilePath -> Maybe String -> FilesMap -> FilesMap
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HM.insert NormalizedFilePath
ncfp Maybe String
hieYaml
               return (IdeResult HscEnvEq
res, [String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
hieYaml [String] -> [String] -> [String]
forall a. [a] -> [a] -> [a]
++ (CradleError -> [String]) -> [CradleError] -> [String]
forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CradleError -> [String]
cradleErrorDependencies [CradleError]
err)

    -- This caches the mapping from hie.yaml + Mod.hs -> [String]
    -- Returns the Ghc session and the cradle dependencies
    let sessionOpts :: (Maybe FilePath, FilePath)
                    -> IO (IdeResult HscEnvEq, [FilePath])
        sessionOpts :: (Maybe String, String) -> IO (IdeResult HscEnvEq, [String])
sessionOpts (Maybe String
hieYaml, String
file) = do
          HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
v <- HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> Maybe
     (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall a. a -> Maybe a -> a
fromMaybe HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall k v. HashMap k v
HM.empty (Maybe
   (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
 -> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
-> (FlagsMap
    -> Maybe
         (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)))
-> FlagsMap
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe String
-> FlagsMap
-> Maybe
     (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Maybe String
hieYaml (FlagsMap
 -> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
-> IO FlagsMap
-> IO
     (HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Var FlagsMap -> IO FlagsMap
forall a. Var a -> IO a
readVar Var FlagsMap
fileToFlags
          String
cfp <- String -> IO String
canonicalizePath String
file
          case NormalizedFilePath
-> HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
-> Maybe (IdeResult HscEnvEq, DependencyInfo)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup (String -> NormalizedFilePath
toNormalizedFilePath' String
cfp) HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo)
v of
            Just (IdeResult HscEnvEq
opts, DependencyInfo
old_di) -> do
              Bool
deps_ok <- DependencyInfo -> IO Bool
checkDependencyInfo DependencyInfo
old_di
              if Bool -> Bool
not Bool
deps_ok
                then do
                  -- If the dependencies are out of date then clear both caches and start
                  -- again.
                  Var FlagsMap -> (FlagsMap -> IO FlagsMap) -> IO ()
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ Var FlagsMap
fileToFlags (IO FlagsMap -> FlagsMap -> IO FlagsMap
forall a b. a -> b -> a
const (FlagsMap -> IO FlagsMap
forall (m :: * -> *) a. Monad m => a -> m a
return FlagsMap
forall k a. Map k a
Map.empty))
                  -- Keep the same name cache
                  Var HieMap -> (HieMap -> IO HieMap) -> IO ()
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ Var HieMap
hscEnvs (HieMap -> IO HieMap
forall (m :: * -> *) a. Monad m => a -> m a
return (HieMap -> IO HieMap) -> (HieMap -> HieMap) -> HieMap -> IO HieMap
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((HscEnv, [RawComponentInfo]) -> (HscEnv, [RawComponentInfo]))
-> Maybe String -> HieMap -> HieMap
forall k a. Ord k => (a -> a) -> k -> Map k a -> Map k a
Map.adjust (\(HscEnv
h, [RawComponentInfo]
_) -> (HscEnv
h, [])) Maybe String
hieYaml )
                  Maybe String -> String -> IO (IdeResult HscEnvEq, [String])
consultCradle Maybe String
hieYaml String
cfp
                else (IdeResult HscEnvEq, [String]) -> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. Monad m => a -> m a
return (IdeResult HscEnvEq
opts, DependencyInfo -> [String]
forall k a. Map k a -> [k]
Map.keys DependencyInfo
old_di)
            Maybe (IdeResult HscEnvEq, DependencyInfo)
Nothing -> Maybe String -> String -> IO (IdeResult HscEnvEq, [String])
consultCradle Maybe String
hieYaml String
cfp

    -- The main function which gets options for a file. We only want one of these running
    -- at a time. Therefore the IORef contains the currently running cradle, if we try
    -- to get some more options then we wait for the currently running action to finish
    -- before attempting to do so.
    let getOptions :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
        getOptions :: String -> IO (IdeResult HscEnvEq, [String])
getOptions String
file = do
            NormalizedFilePath
ncfp <- String -> NormalizedFilePath
toNormalizedFilePath' (String -> NormalizedFilePath)
-> IO String -> IO NormalizedFilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
canonicalizePath String
file
            Maybe (Maybe String)
cachedHieYamlLocation <- NormalizedFilePath -> FilesMap -> Maybe (Maybe String)
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup NormalizedFilePath
ncfp (FilesMap -> Maybe (Maybe String))
-> IO FilesMap -> IO (Maybe (Maybe String))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Var FilesMap -> IO FilesMap
forall a. Var a -> IO a
readVar Var FilesMap
filesMap
            Maybe String
hieYaml <- String -> IO (Maybe String)
cradleLoc String
file
            (Maybe String, String) -> IO (IdeResult HscEnvEq, [String])
sessionOpts (Maybe (Maybe String) -> Maybe String
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe String)
cachedHieYamlLocation Maybe String -> Maybe String -> Maybe String
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
hieYaml, String
file) IO (IdeResult HscEnvEq, [String])
-> (PackageSetupException -> IO (IdeResult HscEnvEq, [String]))
-> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`catch` \PackageSetupException
e ->
                (IdeResult HscEnvEq, [String]) -> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. Monad m => a -> m a
return (([String
-> PackageSetupException
-> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderPackageSetupException String
file PackageSetupException
e], Maybe HscEnvEq
forall a. Maybe a
Nothing), [String] -> (String -> [String]) -> Maybe String -> [String]
forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] String -> [String]
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
hieYaml)

    (String -> IO (IdeResult HscEnvEq, [String]))
-> Action IdeGhcSession
returnWithVersion ((String -> IO (IdeResult HscEnvEq, [String]))
 -> Action IdeGhcSession)
-> (String -> IO (IdeResult HscEnvEq, [String]))
-> Action IdeGhcSession
forall a b. (a -> b) -> a -> b
$ \String
file -> do
      (IdeResult HscEnvEq, [String])
opts <- IO (IdeResult HscEnvEq, [String])
-> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO (IdeResult HscEnvEq, [String])
 -> IO (IdeResult HscEnvEq, [String]))
-> IO (IdeResult HscEnvEq, [String])
-> IO (IdeResult HscEnvEq, [String])
forall a b. (a -> b) -> a -> b
$ IO (IO (IdeResult HscEnvEq, [String]))
-> IO (IdeResult HscEnvEq, [String])
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO (IdeResult HscEnvEq, [String]))
 -> IO (IdeResult HscEnvEq, [String]))
-> IO (IO (IdeResult HscEnvEq, [String]))
-> IO (IdeResult HscEnvEq, [String])
forall a b. (a -> b) -> a -> b
$ IO (IO (IdeResult HscEnvEq, [String]))
-> IO (IO (IdeResult HscEnvEq, [String]))
forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ (IO (IO (IdeResult HscEnvEq, [String]))
 -> IO (IO (IdeResult HscEnvEq, [String])))
-> IO (IO (IdeResult HscEnvEq, [String]))
-> IO (IO (IdeResult HscEnvEq, [String]))
forall a b. (a -> b) -> a -> b
$ Var (Async (IdeResult HscEnvEq, [String]))
-> (Async (IdeResult HscEnvEq, [String])
    -> IO
         (Async (IdeResult HscEnvEq, [String]),
          IO (IdeResult HscEnvEq, [String])))
-> IO (IO (IdeResult HscEnvEq, [String]))
forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var (Async (IdeResult HscEnvEq, [String]))
runningCradle ((Async (IdeResult HscEnvEq, [String])
  -> IO
       (Async (IdeResult HscEnvEq, [String]),
        IO (IdeResult HscEnvEq, [String])))
 -> IO (IO (IdeResult HscEnvEq, [String])))
-> (Async (IdeResult HscEnvEq, [String])
    -> IO
         (Async (IdeResult HscEnvEq, [String]),
          IO (IdeResult HscEnvEq, [String])))
-> IO (IO (IdeResult HscEnvEq, [String]))
forall a b. (a -> b) -> a -> b
$ \Async (IdeResult HscEnvEq, [String])
as -> do
        -- If the cradle is not finished, then wait for it to finish.
        IO (IdeResult HscEnvEq, [String]) -> IO ()
forall (f :: * -> *) a. Functor f => f a -> f ()
void (IO (IdeResult HscEnvEq, [String]) -> IO ())
-> IO (IdeResult HscEnvEq, [String]) -> IO ()
forall a b. (a -> b) -> a -> b
$ Async (IdeResult HscEnvEq, [String])
-> IO (IdeResult HscEnvEq, [String])
forall a. Async a -> IO a
wait Async (IdeResult HscEnvEq, [String])
as
        Async (IdeResult HscEnvEq, [String])
as <- IO (IdeResult HscEnvEq, [String])
-> IO (Async (IdeResult HscEnvEq, [String]))
forall a. IO a -> IO (Async a)
async (IO (IdeResult HscEnvEq, [String])
 -> IO (Async (IdeResult HscEnvEq, [String])))
-> IO (IdeResult HscEnvEq, [String])
-> IO (Async (IdeResult HscEnvEq, [String]))
forall a b. (a -> b) -> a -> b
$ String -> IO (IdeResult HscEnvEq, [String])
getOptions String
file
        return (Async (IdeResult HscEnvEq, [String])
as, Async (IdeResult HscEnvEq, [String])
-> IO (IdeResult HscEnvEq, [String])
forall a. Async a -> IO a
wait Async (IdeResult HscEnvEq, [String])
as)
      pure (IdeResult HscEnvEq, [String])
opts

-- | Run the specific cradle on a specific FilePath via hie-bios.
-- This then builds dependencies or whatever based on the cradle, gets the
-- GHC options/dynflags needed for the session and the GHC library directory

cradleToOptsAndLibDir :: Show a => Cradle a -> FilePath
                      -> IO (Either [CradleError] (ComponentOptions, FilePath))
cradleToOptsAndLibDir :: Cradle a
-> String -> IO (Either [CradleError] (ComponentOptions, String))
cradleToOptsAndLibDir Cradle a
cradle String
file = do
    -- Start off by getting the session options
    let showLine :: String -> IO ()
showLine String
s = Handle -> String -> IO ()
hPutStrLn Handle
stderr (String
"> " String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
s)
    Handle -> String -> IO ()
hPutStrLn Handle
stderr (String -> IO ()) -> String -> IO ()
forall a b. (a -> b) -> a -> b
$ String
"Output from setting up the cradle " String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Cradle a -> String
forall a. Show a => a -> String
show Cradle a
cradle
    CradleLoadResult ComponentOptions
cradleRes <- CradleAction a
-> (String -> IO ())
-> String
-> IO (CradleLoadResult ComponentOptions)
forall a.
CradleAction a
-> (String -> IO ())
-> String
-> IO (CradleLoadResult ComponentOptions)
runCradle (Cradle a -> CradleAction a
forall a. Cradle a -> CradleAction a
cradleOptsProg Cradle a
cradle) String -> IO ()
showLine String
file
    case CradleLoadResult ComponentOptions
cradleRes of
        CradleSuccess ComponentOptions
r -> do
            -- Now get the GHC lib dir
            CradleLoadResult String
libDirRes <- Cradle a -> IO (CradleLoadResult String)
forall a. Cradle a -> IO (CradleLoadResult String)
getRuntimeGhcLibDir Cradle a
cradle
            case CradleLoadResult String
libDirRes of
                -- This is the successful path
                CradleSuccess String
libDir -> Either [CradleError] (ComponentOptions, String)
-> IO (Either [CradleError] (ComponentOptions, String))
forall (f :: * -> *) a. Applicative f => a -> f a
pure ((ComponentOptions, String)
-> Either [CradleError] (ComponentOptions, String)
forall a b. b -> Either a b
Right (ComponentOptions
r, String
libDir))
                CradleFail CradleError
err       -> Either [CradleError] (ComponentOptions, String)
-> IO (Either [CradleError] (ComponentOptions, String))
forall (m :: * -> *) a. Monad m => a -> m a
return ([CradleError] -> Either [CradleError] (ComponentOptions, String)
forall a b. a -> Either a b
Left [CradleError
err])
                -- For the None cradle perhaps we still want to report an Info
                -- message about the fact that the file is being ignored.
                CradleLoadResult String
CradleNone           -> Either [CradleError] (ComponentOptions, String)
-> IO (Either [CradleError] (ComponentOptions, String))
forall (m :: * -> *) a. Monad m => a -> m a
return ([CradleError] -> Either [CradleError] (ComponentOptions, String)
forall a b. a -> Either a b
Left [])

        CradleFail CradleError
err -> Either [CradleError] (ComponentOptions, String)
-> IO (Either [CradleError] (ComponentOptions, String))
forall (m :: * -> *) a. Monad m => a -> m a
return ([CradleError] -> Either [CradleError] (ComponentOptions, String)
forall a b. a -> Either a b
Left [CradleError
err])
        -- Same here
        CradleLoadResult ComponentOptions
CradleNone -> Either [CradleError] (ComponentOptions, String)
-> IO (Either [CradleError] (ComponentOptions, String))
forall (m :: * -> *) a. Monad m => a -> m a
return ([CradleError] -> Either [CradleError] (ComponentOptions, String)
forall a b. a -> Either a b
Left [])

emptyHscEnv :: IORef NameCache -> FilePath -> IO HscEnv
emptyHscEnv :: IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
nc String
libDir = do
    HscEnv
env <- Maybe String -> Ghc HscEnv -> IO HscEnv
forall a. Maybe String -> Ghc a -> IO a
runGhc (String -> Maybe String
forall a. a -> Maybe a
Just String
libDir) Ghc HscEnv
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
#if !MIN_VERSION_ghc(9,0,0)
    -- This causes ghc9 to crash with the error:
    -- Couldn't find a target code interpreter. Try with -fexternal-interpreter
    HscEnv -> IO ()
initDynLinker HscEnv
env
#endif
    pure $ IORef NameCache -> HscEnv -> HscEnv
setNameCache IORef NameCache
nc HscEnv
env{ hsc_dflags :: DynFlags
hsc_dflags = (HscEnv -> DynFlags
hsc_dflags HscEnv
env){useUnicode :: Bool
useUnicode = Bool
True } }

data TargetDetails = TargetDetails
  {
      TargetDetails -> Target
targetTarget    :: !Target,
      TargetDetails -> IdeResult HscEnvEq
targetEnv       :: !(IdeResult HscEnvEq),
      TargetDetails -> DependencyInfo
targetDepends   :: !DependencyInfo,
      TargetDetails -> [NormalizedFilePath]
targetLocations :: ![NormalizedFilePath]
  }

fromTargetId :: [FilePath]          -- ^ import paths
             -> [String]            -- ^ extensions to consider
             -> TargetId
             -> IdeResult HscEnvEq
             -> DependencyInfo
             -> IO [TargetDetails]
-- For a target module we consider all the import paths
fromTargetId :: [String]
-> [String]
-> TargetId
-> IdeResult HscEnvEq
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId [String]
is [String]
exts (GHC.TargetModule ModuleName
mod) IdeResult HscEnvEq
env DependencyInfo
dep = do
    let fps :: [String]
fps = [String
i String -> String -> String
</> ModuleName -> String
moduleNameSlashes ModuleName
mod String -> String -> String
-<.> String
ext String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
boot
              | String
ext <- [String]
exts
              , String
i <- [String]
is
              , String
boot <- [String
"", String
"-boot"]
              ]
    [NormalizedFilePath]
locs <- (String -> IO NormalizedFilePath)
-> [String] -> IO [NormalizedFilePath]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM ((String -> NormalizedFilePath)
-> IO String -> IO NormalizedFilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NormalizedFilePath
toNormalizedFilePath' (IO String -> IO NormalizedFilePath)
-> (String -> IO String) -> String -> IO NormalizedFilePath
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO String
canonicalizePath) [String]
fps
    return [Target
-> IdeResult HscEnvEq
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (ModuleName -> Target
TargetModule ModuleName
mod) IdeResult HscEnvEq
env DependencyInfo
dep [NormalizedFilePath]
locs]
-- For a 'TargetFile' we consider all the possible module names
fromTargetId [String]
_ [String]
_ (GHC.TargetFile String
f Maybe Phase
_) IdeResult HscEnvEq
env DependencyInfo
deps = do
    NormalizedFilePath
nf <- String -> NormalizedFilePath
toNormalizedFilePath' (String -> NormalizedFilePath)
-> IO String -> IO NormalizedFilePath
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
canonicalizePath String
f
    return [Target
-> IdeResult HscEnvEq
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (NormalizedFilePath -> Target
TargetFile NormalizedFilePath
nf) IdeResult HscEnvEq
env DependencyInfo
deps [NormalizedFilePath
nf]]

toFlagsMap :: TargetDetails -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap :: TargetDetails
-> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap TargetDetails{[NormalizedFilePath]
IdeResult HscEnvEq
DependencyInfo
Target
targetLocations :: [NormalizedFilePath]
targetDepends :: DependencyInfo
targetEnv :: IdeResult HscEnvEq
targetTarget :: Target
targetLocations :: TargetDetails -> [NormalizedFilePath]
targetDepends :: TargetDetails -> DependencyInfo
targetEnv :: TargetDetails -> IdeResult HscEnvEq
targetTarget :: TargetDetails -> Target
..} =
    [ (NormalizedFilePath
l, (IdeResult HscEnvEq
targetEnv, DependencyInfo
targetDepends)) | NormalizedFilePath
l <-  [NormalizedFilePath]
targetLocations]


setNameCache :: IORef NameCache -> HscEnv -> HscEnv
setNameCache :: IORef NameCache -> HscEnv -> HscEnv
setNameCache IORef NameCache
nc HscEnv
hsc = HscEnv
hsc { hsc_NC :: IORef NameCache
hsc_NC = IORef NameCache
nc }

-- | Create a mapping from FilePaths to HscEnvEqs
newComponentCache
         :: Logger
         -> [String]       -- File extensions to consider
         -> Maybe FilePath -- Path to cradle
         -> NormalizedFilePath -- Path to file that caused the creation of this component
         -> HscEnv
         -> [(InstalledUnitId, DynFlags)]
         -> ComponentInfo
         -> IO ( [TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
newComponentCache :: Logger
-> [String]
-> Maybe String
-> NormalizedFilePath
-> HscEnv
-> [(InstalledUnitId, DynFlags)]
-> ComponentInfo
-> IO ([TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
newComponentCache Logger
logger [String]
exts Maybe String
cradlePath NormalizedFilePath
cfp HscEnv
hsc_env [(InstalledUnitId, DynFlags)]
uids ComponentInfo
ci = do
    let df :: DynFlags
df = ComponentInfo -> DynFlags
componentDynFlags ComponentInfo
ci
    let hscEnv' :: HscEnv
hscEnv' = HscEnv
hsc_env { hsc_dflags :: DynFlags
hsc_dflags = DynFlags
df
                          , hsc_IC :: InteractiveContext
hsc_IC = (HscEnv -> InteractiveContext
hsc_IC HscEnv
hsc_env) { ic_dflags :: DynFlags
ic_dflags = DynFlags
df } }

    let newFunc :: HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
newFunc = (HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq)
-> (String
    -> HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq)
-> Maybe String
-> HscEnv
-> [(InstalledUnitId, DynFlags)]
-> IO HscEnvEq
forall b a. b -> (a -> b) -> Maybe a -> b
maybe HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
newHscEnvEqPreserveImportPaths String -> HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
newHscEnvEq Maybe String
cradlePath
    HscEnvEq
henv <- HscEnv -> [(InstalledUnitId, DynFlags)] -> IO HscEnvEq
newFunc HscEnv
hscEnv' [(InstalledUnitId, DynFlags)]
uids
    let targetEnv :: IdeResult HscEnvEq
targetEnv = ([], HscEnvEq -> Maybe HscEnvEq
forall a. a -> Maybe a
Just HscEnvEq
henv)
        targetDepends :: DependencyInfo
targetDepends = ComponentInfo -> DependencyInfo
componentDependencyInfo ComponentInfo
ci
        res :: (IdeResult HscEnvEq, DependencyInfo)
res = (IdeResult HscEnvEq
targetEnv, DependencyInfo
targetDepends)
    Logger -> Text -> IO ()
logDebug Logger
logger (Text
"New Component Cache HscEnvEq: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack ((IdeResult HscEnvEq, DependencyInfo) -> String
forall a. Show a => a -> String
show (IdeResult HscEnvEq, DependencyInfo)
res))

    let mk :: Target -> IO [TargetDetails]
mk Target
t = [String]
-> [String]
-> TargetId
-> IdeResult HscEnvEq
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId (DynFlags -> [String]
importPaths DynFlags
df) [String]
exts (Target -> TargetId
targetId Target
t) IdeResult HscEnvEq
targetEnv DependencyInfo
targetDepends
    [TargetDetails]
ctargets <- (Target -> IO [TargetDetails]) -> [Target] -> IO [TargetDetails]
forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM Target -> IO [TargetDetails]
mk (ComponentInfo -> [Target]
componentTargets ComponentInfo
ci)

    -- A special target for the file which caused this wonderful
    -- component to be created. In case the cradle doesn't list all the targets for
    -- the component, in which case things will be horribly broken anyway.
    -- Otherwise, we will immediately attempt to reload this module which
    -- causes an infinite loop and high CPU usage.
    let special_target :: TargetDetails
special_target = Target
-> IdeResult HscEnvEq
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (NormalizedFilePath -> Target
TargetFile NormalizedFilePath
cfp) IdeResult HscEnvEq
targetEnv DependencyInfo
targetDepends [ComponentInfo -> NormalizedFilePath
componentFP ComponentInfo
ci]
    return (TargetDetails
special_targetTargetDetails -> [TargetDetails] -> [TargetDetails]
forall a. a -> [a] -> [a]
:[TargetDetails]
ctargets, (IdeResult HscEnvEq, DependencyInfo)
res)

{- Note [Avoiding bad interface files]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
Originally, we set the cache directory for the various components once
on the first occurrence of the component.
This works fine if these components have no references to each other,
but you have components that depend on each other, the interface files are
updated for each component.
After restarting the session and only opening the component that depended
on the other, suddenly the interface files of this component are stale.
However, from the point of view of `ghcide`, they do not look stale,
thus, not regenerated and the IDE shows weird errors such as:
```
typecheckIface
Declaration for Rep_ClientRunFlags
Axiom branches Rep_ClientRunFlags:
  Failed to load interface for ‘Distribution.Simple.Flag’
  Use -v to see a list of the files searched for.
```
and
```
expectJust checkFamInstConsistency
CallStack (from HasCallStack):
  error, called at compiler\\utils\\Maybes.hs:55:27 in ghc:Maybes
  expectJust, called at compiler\\typecheck\\FamInst.hs:461:30 in ghc:FamInst
```

To mitigate this, we set the cache directory for each component dependent
on the components of the current `HscEnv`, additionally to the component options
of the respective components.
Assume two components, c1, c2, where c2 depends on c1, and the options of the
respective components are co1, co2.
If we want to load component c2, followed by c1, we set the cache directory for
each component in this way:

  * Load component c2
    * (Cache Directory State)
        - name of c2 + co2
  * Load component c1
    * (Cache Directory State)
        - name of c2 + name of c1 + co2
        - name of c2 + name of c1 + co1

Overall, we created three cache directories. If we opened c1 first, then we
create a fourth cache directory.
This makes sure that interface files are always correctly updated.

Since this causes a lot of recompilation, we only update the cache-directory,
if the dependencies of a component have really changed.
E.g. when you load two executables, they can not depend on each other. They
should be filtered out, such that we dont have to re-compile everything.
-}

-- | Set the cache-directory based on the ComponentOptions and a list of
-- internal packages.
-- For the exact reason, see Note [Avoiding bad interface files].
setCacheDirs :: MonadIO m => Logger -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs :: Logger -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs Logger
logger CacheDirs{Maybe String
oCacheDir :: Maybe String
hieCacheDir :: Maybe String
hiCacheDir :: Maybe String
oCacheDir :: CacheDirs -> Maybe String
hieCacheDir :: CacheDirs -> Maybe String
hiCacheDir :: CacheDirs -> Maybe String
..} DynFlags
dflags = do
    IO () -> m ()
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO () -> m ()) -> IO () -> m ()
forall a b. (a -> b) -> a -> b
$ Logger -> Text -> IO ()
logInfo Logger
logger (Text -> IO ()) -> Text -> IO ()
forall a b. (a -> b) -> a -> b
$ Text
"Using interface files cache dir: " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (String -> Maybe String -> String
forall a. a -> Maybe a -> a
fromMaybe String
cacheDir Maybe String
hiCacheDir)
    pure $ DynFlags
dflags
          DynFlags -> (DynFlags -> DynFlags) -> DynFlags
forall a b. a -> (a -> b) -> b
& (DynFlags -> DynFlags)
-> (String -> DynFlags -> DynFlags)
-> Maybe String
-> DynFlags
-> DynFlags
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DynFlags -> DynFlags
forall a. a -> a
id String -> DynFlags -> DynFlags
setHiDir Maybe String
hiCacheDir
          DynFlags -> (DynFlags -> DynFlags) -> DynFlags
forall a b. a -> (a -> b) -> b
& (DynFlags -> DynFlags)
-> (String -> DynFlags -> DynFlags)
-> Maybe String
-> DynFlags
-> DynFlags
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DynFlags -> DynFlags
forall a. a -> a
id String -> DynFlags -> DynFlags
setHieDir Maybe String
hieCacheDir
          DynFlags -> (DynFlags -> DynFlags) -> DynFlags
forall a b. a -> (a -> b) -> b
& (DynFlags -> DynFlags)
-> (String -> DynFlags -> DynFlags)
-> Maybe String
-> DynFlags
-> DynFlags
forall b a. b -> (a -> b) -> Maybe a -> b
maybe DynFlags -> DynFlags
forall a. a -> a
id String -> DynFlags -> DynFlags
setODir Maybe String
oCacheDir


renderCradleError :: NormalizedFilePath -> CradleError -> FileDiagnostic
renderCradleError :: NormalizedFilePath
-> CradleError -> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderCradleError NormalizedFilePath
nfp (CradleError [String]
_ ExitCode
_ec [String]
t) =
  Maybe Text
-> Maybe DiagnosticSeverity
-> NormalizedFilePath
-> Text
-> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
forall a.
Maybe Text
-> Maybe DiagnosticSeverity
-> a
-> Text
-> (a, ShowDiagnostic, Diagnostic)
ideErrorWithSource (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"cradle") (DiagnosticSeverity -> Maybe DiagnosticSeverity
forall a. a -> Maybe a
Just DiagnosticSeverity
DsError) NormalizedFilePath
nfp ([Text] -> Text
T.unlines ((String -> Text) -> [String] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map String -> Text
T.pack [String]
t))

-- See Note [Multi Cradle Dependency Info]
type DependencyInfo = Map.Map FilePath (Maybe UTCTime)
type HieMap = Map.Map (Maybe FilePath) (HscEnv, [RawComponentInfo])
-- | Maps a "hie.yaml" location to all its Target Filepaths and options.
type FlagsMap = Map.Map (Maybe FilePath) (HM.HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
-- | Maps a Filepath to its respective "hie.yaml" location.
-- It aims to be the reverse of 'FlagsMap'.
type FilesMap = HM.HashMap NormalizedFilePath (Maybe FilePath)

-- This is pristine information about a component
data RawComponentInfo = RawComponentInfo
  { RawComponentInfo -> InstalledUnitId
rawComponentUnitId         :: InstalledUnitId
  -- | Unprocessed DynFlags. Contains inplace packages such as libraries.
  -- We do not want to use them unprocessed.
  , RawComponentInfo -> DynFlags
rawComponentDynFlags       :: DynFlags
  -- | All targets of this components.
  , RawComponentInfo -> [Target]
rawComponentTargets        :: [GHC.Target]
  -- | Filepath which caused the creation of this component
  , RawComponentInfo -> NormalizedFilePath
rawComponentFP             :: NormalizedFilePath
  -- | Component Options used to load the component.
  , RawComponentInfo -> ComponentOptions
rawComponentCOptions       :: ComponentOptions
  -- | Maps cradle dependencies, such as `stack.yaml`, or `.cabal` file
  -- to last modification time. See Note [Multi Cradle Dependency Info].
  , RawComponentInfo -> DependencyInfo
rawComponentDependencyInfo :: DependencyInfo
  }

-- This is processed information about the component, in particular the dynflags will be modified.
data ComponentInfo = ComponentInfo
  { ComponentInfo -> InstalledUnitId
componentUnitId         :: InstalledUnitId
  -- | Processed DynFlags. Does not contain inplace packages such as local
  -- libraries. Can be used to actually load this Component.
  , ComponentInfo -> DynFlags
componentDynFlags       :: DynFlags
  -- | Internal units, such as local libraries, that this component
  -- is loaded with. These have been extracted from the original
  -- ComponentOptions.
  , ComponentInfo -> [InstalledUnitId]
_componentInternalUnits :: [InstalledUnitId]
  -- | All targets of this components.
  , ComponentInfo -> [Target]
componentTargets        :: [GHC.Target]
  -- | Filepath which caused the creation of this component
  , ComponentInfo -> NormalizedFilePath
componentFP             :: NormalizedFilePath
  -- | Component Options used to load the component.
  , ComponentInfo -> ComponentOptions
_componentCOptions      :: ComponentOptions
  -- | Maps cradle dependencies, such as `stack.yaml`, or `.cabal` file
  -- to last modification time. See Note [Multi Cradle Dependency Info]
  , ComponentInfo -> DependencyInfo
componentDependencyInfo :: DependencyInfo
  }

-- | Check if any dependency has been modified lately.
checkDependencyInfo :: DependencyInfo -> IO Bool
checkDependencyInfo :: DependencyInfo -> IO Bool
checkDependencyInfo DependencyInfo
old_di = do
  DependencyInfo
di <- [String] -> IO DependencyInfo
getDependencyInfo (DependencyInfo -> [String]
forall k a. Map k a -> [k]
Map.keys DependencyInfo
old_di)
  return (DependencyInfo
di DependencyInfo -> DependencyInfo -> Bool
forall a. Eq a => a -> a -> Bool
== DependencyInfo
old_di)

-- Note [Multi Cradle Dependency Info]
-- ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
-- Why do we implement our own file modification tracking here?
-- The primary reason is that the custom caching logic is quite complicated and going into shake
-- adds even more complexity and more indirection. I did try for about 5 hours to work out how to
-- use shake rules rather than IO but eventually gave up.

-- | Computes a mapping from a filepath to its latest modification date.
-- See Note [Multi Cradle Dependency Info] why we do this ourselves instead
-- of letting shake take care of it.
getDependencyInfo :: [FilePath] -> IO DependencyInfo
getDependencyInfo :: [String] -> IO DependencyInfo
getDependencyInfo [String]
fs = [(String, Maybe UTCTime)] -> DependencyInfo
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList ([(String, Maybe UTCTime)] -> DependencyInfo)
-> IO [(String, Maybe UTCTime)] -> IO DependencyInfo
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (String -> IO (String, Maybe UTCTime))
-> [String] -> IO [(String, Maybe UTCTime)]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM String -> IO (String, Maybe UTCTime)
do_one [String]
fs

  where
    tryIO :: IO a -> IO (Either IOException a)
    tryIO :: IO a -> IO (Either IOException a)
tryIO = IO a -> IO (Either IOException a)
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
try

    do_one :: FilePath -> IO (FilePath, Maybe UTCTime)
    do_one :: String -> IO (String, Maybe UTCTime)
do_one String
fp = (String
fp,) (Maybe UTCTime -> (String, Maybe UTCTime))
-> (Either IOException UTCTime -> Maybe UTCTime)
-> Either IOException UTCTime
-> (String, Maybe UTCTime)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Either IOException UTCTime -> Maybe UTCTime
forall a b. Either a b -> Maybe b
eitherToMaybe (Either IOException UTCTime -> (String, Maybe UTCTime))
-> IO (Either IOException UTCTime) -> IO (String, Maybe UTCTime)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO UTCTime -> IO (Either IOException UTCTime)
forall a. IO a -> IO (Either IOException a)
tryIO (String -> IO UTCTime
getModificationTime String
fp)

-- | This function removes all the -package flags which refer to packages we
-- are going to deal with ourselves. For example, if a executable depends
-- on a library component, then this function will remove the library flag
-- from the package flags for the executable
--
-- There are several places in GHC (for example the call to hptInstances in
-- tcRnImports) which assume that all modules in the HPT have the same unit
-- ID. Therefore we create a fake one and give them all the same unit id.
removeInplacePackages
    :: InstalledUnitId     -- ^ fake uid to use for our internal component
    -> [InstalledUnitId]
    -> DynFlags
    -> (DynFlags, [InstalledUnitId])
removeInplacePackages :: InstalledUnitId
-> [InstalledUnitId] -> DynFlags -> (DynFlags, [InstalledUnitId])
removeInplacePackages InstalledUnitId
fake_uid [InstalledUnitId]
us DynFlags
df = (InstalledUnitId -> DynFlags -> DynFlags
setThisInstalledUnitId InstalledUnitId
fake_uid (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
                                       DynFlags
df { packageFlags :: [PackageFlag]
packageFlags = [PackageFlag]
ps }, [InstalledUnitId]
uids)
  where
    ([InstalledUnitId]
uids, [PackageFlag]
ps) = [Either InstalledUnitId PackageFlag]
-> ([InstalledUnitId], [PackageFlag])
forall a b. [Either a b] -> ([a], [b])
partitionEithers ((PackageFlag -> Either InstalledUnitId PackageFlag)
-> [PackageFlag] -> [Either InstalledUnitId PackageFlag]
forall a b. (a -> b) -> [a] -> [b]
map PackageFlag -> Either InstalledUnitId PackageFlag
go (DynFlags -> [PackageFlag]
packageFlags DynFlags
df))
    go :: PackageFlag -> Either InstalledUnitId PackageFlag
go p :: PackageFlag
p@(ExposePackage String
_ (UnitIdArg UnitId
u) ModRenaming
_) = if UnitId -> InstalledUnitId
GHC.toInstalledUnitId UnitId
u InstalledUnitId -> [InstalledUnitId] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [InstalledUnitId]
us
                                                  then InstalledUnitId -> Either InstalledUnitId PackageFlag
forall a b. a -> Either a b
Left (UnitId -> InstalledUnitId
GHC.toInstalledUnitId UnitId
u)
                                                  else PackageFlag -> Either InstalledUnitId PackageFlag
forall a b. b -> Either a b
Right PackageFlag
p
    go PackageFlag
p = PackageFlag -> Either InstalledUnitId PackageFlag
forall a b. b -> Either a b
Right PackageFlag
p

-- | Memoize an IO function, with the characteristics:
--
--   * If multiple people ask for a result simultaneously, make sure you only compute it once.
--
--   * If there are exceptions, repeatedly reraise them.
--
--   * If the caller is aborted (async exception) finish computing it anyway.
memoIO :: Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO :: (a -> IO b) -> IO (a -> IO b)
memoIO a -> IO b
op = do
    Var (Map a (IO b))
ref <- Map a (IO b) -> IO (Var (Map a (IO b)))
forall a. a -> IO (Var a)
newVar Map a (IO b)
forall k a. Map k a
Map.empty
    return $ \a
k -> IO (IO b) -> IO b
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join (IO (IO b) -> IO b) -> IO (IO b) -> IO b
forall a b. (a -> b) -> a -> b
$ IO (IO b) -> IO (IO b)
forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ (IO (IO b) -> IO (IO b)) -> IO (IO b) -> IO (IO b)
forall a b. (a -> b) -> a -> b
$ Var (Map a (IO b))
-> (Map a (IO b) -> IO (Map a (IO b), IO b)) -> IO (IO b)
forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var (Map a (IO b))
ref ((Map a (IO b) -> IO (Map a (IO b), IO b)) -> IO (IO b))
-> (Map a (IO b) -> IO (Map a (IO b), IO b)) -> IO (IO b)
forall a b. (a -> b) -> a -> b
$ \Map a (IO b)
mp ->
        case a -> Map a (IO b) -> Maybe (IO b)
forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup a
k Map a (IO b)
mp of
            Maybe (IO b)
Nothing -> do
                IO b
res <- IO b -> IO (IO b)
forall a. IO a -> IO (IO a)
onceFork (IO b -> IO (IO b)) -> IO b -> IO (IO b)
forall a b. (a -> b) -> a -> b
$ a -> IO b
op a
k
                return (a -> IO b -> Map a (IO b) -> Map a (IO b)
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert a
k IO b
res Map a (IO b)
mp, IO b
res)
            Just IO b
res -> (Map a (IO b), IO b) -> IO (Map a (IO b), IO b)
forall (m :: * -> *) a. Monad m => a -> m a
return (Map a (IO b)
mp, IO b
res)

-- | Throws if package flags are unsatisfiable
setOptions :: GhcMonad m => ComponentOptions -> DynFlags -> m (DynFlags, [GHC.Target])
setOptions :: ComponentOptions -> DynFlags -> m (DynFlags, [Target])
setOptions (ComponentOptions [String]
theOpts String
compRoot [String]
_) DynFlags
dflags = do
    (DynFlags
dflags', [Target]
targets') <- [String] -> DynFlags -> m (DynFlags, [Target])
forall (m :: * -> *).
GhcMonad m =>
[String] -> DynFlags -> m (DynFlags, [Target])
addCmdOpts [String]
theOpts DynFlags
dflags
    let targets :: [Target]
targets = String -> [Target] -> [Target]
makeTargetsAbsolute String
compRoot [Target]
targets'
    let dflags'' :: DynFlags
dflags'' =
          DynFlags -> DynFlags
disableWarningsAsErrors (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          -- disabled, generated directly by ghcide instead
          (DynFlags -> GeneralFlag -> DynFlags)
-> GeneralFlag -> DynFlags -> DynFlags
forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> GeneralFlag -> DynFlags
gopt_unset GeneralFlag
Opt_WriteInterface (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          -- disabled, generated directly by ghcide instead
          -- also, it can confuse the interface stale check
          DynFlags -> DynFlags
dontWriteHieFiles (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          DynFlags -> DynFlags
setIgnoreInterfacePragmas (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          DynFlags -> DynFlags
setLinkerOptions (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          DynFlags -> DynFlags
disableOptimisation (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          DynFlags -> DynFlags
setUpTypedHoles (DynFlags -> DynFlags) -> DynFlags -> DynFlags
forall a b. (a -> b) -> a -> b
$
          String -> DynFlags -> DynFlags
makeDynFlagsAbsolute String
compRoot DynFlags
dflags'
    -- initPackages parses the -package flags and
    -- sets up the visibility for each component.
    -- Throws if a -package flag cannot be satisfied.
    DynFlags
final_df <- IO DynFlags -> m DynFlags
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (IO DynFlags -> m DynFlags) -> IO DynFlags -> m DynFlags
forall a b. (a -> b) -> a -> b
$ IO DynFlags -> IO DynFlags
forall a. IO a -> IO a
wrapPackageSetupException (IO DynFlags -> IO DynFlags) -> IO DynFlags -> IO DynFlags
forall a b. (a -> b) -> a -> b
$ DynFlags -> IO DynFlags
initUnits DynFlags
dflags''
    return (DynFlags
final_df, [Target]
targets)

-- we don't want to generate object code so we compile to bytecode
-- (HscInterpreted) which implies LinkInMemory
-- HscInterpreted
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions :: DynFlags -> DynFlags
setLinkerOptions DynFlags
df = DynFlags
df {
    ghcLink :: GhcLink
ghcLink   = GhcLink
LinkInMemory
  , hscTarget :: HscTarget
hscTarget = HscTarget
HscNothing
  , ghcMode :: GhcMode
ghcMode = GhcMode
CompManager
  }

setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas :: DynFlags -> DynFlags
setIgnoreInterfacePragmas DynFlags
df =
    DynFlags -> GeneralFlag -> DynFlags
gopt_set (DynFlags -> GeneralFlag -> DynFlags
gopt_set DynFlags
df GeneralFlag
Opt_IgnoreInterfacePragmas) GeneralFlag
Opt_IgnoreOptimChanges

disableOptimisation :: DynFlags -> DynFlags
disableOptimisation :: DynFlags -> DynFlags
disableOptimisation DynFlags
df = Int -> DynFlags -> DynFlags
updOptLevel Int
0 DynFlags
df

setHiDir :: FilePath -> DynFlags -> DynFlags
setHiDir :: String -> DynFlags -> DynFlags
setHiDir String
f DynFlags
d =
    -- override user settings to avoid conflicts leading to recompilation
    DynFlags
d { hiDir :: Maybe String
hiDir      = String -> Maybe String
forall a. a -> Maybe a
Just String
f}

setODir :: FilePath -> DynFlags -> DynFlags
setODir :: String -> DynFlags -> DynFlags
setODir String
f DynFlags
d =
    -- override user settings to avoid conflicts leading to recompilation
    DynFlags
d { objectDir :: Maybe String
objectDir = String -> Maybe String
forall a. a -> Maybe a
Just String
f}

getCacheDirsDefault :: String -> [String] -> IO CacheDirs
getCacheDirsDefault :: String -> [String] -> IO CacheDirs
getCacheDirsDefault String
prefix [String]
opts = do
    Maybe String
dir <- String -> Maybe String
forall a. a -> Maybe a
Just (String -> Maybe String) -> IO String -> IO (Maybe String)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XdgDirectory -> String -> IO String
getXdgDirectory XdgDirectory
XdgCache (String
cacheDir String -> String -> String
</> String
prefix String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"-" String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
opts_hash)
    return $ Maybe String -> Maybe String -> Maybe String -> CacheDirs
CacheDirs Maybe String
dir Maybe String
dir Maybe String
dir
    where
        -- Create a unique folder per set of different GHC options, assuming that each different set of
        -- GHC options will create incompatible interface files.
        opts_hash :: String
opts_hash = ByteString -> String
B.unpack (ByteString -> String) -> ByteString -> String
forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
B16.encode (ByteString -> ByteString) -> ByteString -> ByteString
forall a b. (a -> b) -> a -> b
$ Ctx -> ByteString
H.finalize (Ctx -> ByteString) -> Ctx -> ByteString
forall a b. (a -> b) -> a -> b
$ Ctx -> [ByteString] -> Ctx
H.updates Ctx
H.init ((String -> ByteString) -> [String] -> [ByteString]
forall a b. (a -> b) -> [a] -> [b]
map String -> ByteString
B.pack [String]
opts)

-- | Sub directory for the cache path
cacheDir :: String
cacheDir :: String
cacheDir = String
"ghcide"

implicitCradleWarning :: FilePath -> T.Text
implicitCradleWarning :: String -> Text
implicitCradleWarning String
fp =
  Text
"No [cradle](https://github.com/mpickering/hie-bios#hie-bios) found for "
  Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
fp Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
  Text
".\n Proceeding with [implicit cradle](https://hackage.haskell.org/package/implicit-hie).\n"Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
  Text
"You should ignore this message, unless you see a 'Multi Cradle: No prefixes matched' error."
----------------------------------------------------------------------------------------------------

data PackageSetupException
    = PackageSetupException
        { PackageSetupException -> String
message     :: !String
        }
    | GhcVersionMismatch
        { PackageSetupException -> Version
compileTime :: !Version
        , PackageSetupException -> Version
runTime     :: !Version
        }
    | PackageCheckFailed !NotCompatibleReason
    deriving (PackageSetupException -> PackageSetupException -> Bool
(PackageSetupException -> PackageSetupException -> Bool)
-> (PackageSetupException -> PackageSetupException -> Bool)
-> Eq PackageSetupException
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: PackageSetupException -> PackageSetupException -> Bool
$c/= :: PackageSetupException -> PackageSetupException -> Bool
== :: PackageSetupException -> PackageSetupException -> Bool
$c== :: PackageSetupException -> PackageSetupException -> Bool
Eq, Int -> PackageSetupException -> String -> String
[PackageSetupException] -> String -> String
PackageSetupException -> String
(Int -> PackageSetupException -> String -> String)
-> (PackageSetupException -> String)
-> ([PackageSetupException] -> String -> String)
-> Show PackageSetupException
forall a.
(Int -> a -> String -> String)
-> (a -> String) -> ([a] -> String -> String) -> Show a
showList :: [PackageSetupException] -> String -> String
$cshowList :: [PackageSetupException] -> String -> String
show :: PackageSetupException -> String
$cshow :: PackageSetupException -> String
showsPrec :: Int -> PackageSetupException -> String -> String
$cshowsPrec :: Int -> PackageSetupException -> String -> String
Show, Typeable)

instance Exception PackageSetupException

-- | Wrap any exception as a 'PackageSetupException'
wrapPackageSetupException :: IO a -> IO a
wrapPackageSetupException :: IO a -> IO a
wrapPackageSetupException = (SomeException -> IO a) -> IO a -> IO a
forall (m :: * -> *) a.
MonadCatch m =>
(SomeException -> m a) -> m a -> m a
handleAny ((SomeException -> IO a) -> IO a -> IO a)
-> (SomeException -> IO a) -> IO a -> IO a
forall a b. (a -> b) -> a -> b
$ \case
  SomeException
e | Just (PackageSetupException
pkgE :: PackageSetupException) <- SomeException -> Maybe PackageSetupException
forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e -> PackageSetupException -> IO a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO PackageSetupException
pkgE
  SomeException
e -> (PackageSetupException -> IO a
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO (PackageSetupException -> IO a)
-> (SomeException -> PackageSetupException)
-> SomeException
-> IO a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PackageSetupException
PackageSetupException (String -> PackageSetupException)
-> (SomeException -> String)
-> SomeException
-> PackageSetupException
forall b c a. (b -> c) -> (a -> b) -> a -> c
. SomeException -> String
forall a. Show a => a -> String
show) SomeException
e

showPackageSetupException :: PackageSetupException -> String
showPackageSetupException :: PackageSetupException -> String
showPackageSetupException GhcVersionMismatch{Version
runTime :: Version
compileTime :: Version
runTime :: PackageSetupException -> Version
compileTime :: PackageSetupException -> Version
..} = [String] -> String
unwords
    [String
"ghcide compiled against GHC"
    ,Version -> String
showVersion Version
compileTime
    ,String
"but currently using"
    ,Version -> String
showVersion Version
runTime
    ,String
"\nThis is unsupported, ghcide must be compiled with the same GHC version as the project."
    ]
showPackageSetupException PackageSetupException{String
message :: String
message :: PackageSetupException -> String
..} = [String] -> String
unwords
    [ String
"ghcide compiled by GHC", Version -> String
showVersion Version
compilerVersion
    , String
"failed to load packages:", String
message String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"."
    , String
"\nPlease ensure that ghcide is compiled with the same GHC installation as the project."]
showPackageSetupException (PackageCheckFailed PackageVersionMismatch{String
Version
$sel:compileTime:PackageVersionMismatch :: NotCompatibleReason -> Version
$sel:runTime:PackageVersionMismatch :: NotCompatibleReason -> Version
$sel:packageName:PackageVersionMismatch :: NotCompatibleReason -> String
packageName :: String
runTime :: Version
compileTime :: Version
..}) = [String] -> String
unwords
    [String
"ghcide compiled with package "
    , String
packageName String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime
    ,String
"but project uses package"
    , String
packageName String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
runTime
    ,String
"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project."
    ]
showPackageSetupException (PackageCheckFailed BasePackageAbiMismatch{String
Version
$sel:compileTimeAbi:PackageVersionMismatch :: NotCompatibleReason -> String
$sel:runTimeAbi:PackageVersionMismatch :: NotCompatibleReason -> String
compileTime :: Version
runTimeAbi :: String
compileTimeAbi :: String
$sel:compileTime:PackageVersionMismatch :: NotCompatibleReason -> Version
..}) = [String] -> String
unwords
    [String
"ghcide compiled with base-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
compileTimeAbi
    ,String
"but project uses base-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
"-" String -> String -> String
forall a. Semigroup a => a -> a -> a
<> String
runTimeAbi
    ,String
"\nThis is unsupported, ghcide must be compiled with the same GHC installation as the project."
    ]

renderPackageSetupException :: FilePath -> PackageSetupException -> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderPackageSetupException :: String
-> PackageSetupException
-> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
renderPackageSetupException String
fp PackageSetupException
e =
    Maybe Text
-> Maybe DiagnosticSeverity
-> NormalizedFilePath
-> Text
-> (NormalizedFilePath, ShowDiagnostic, Diagnostic)
forall a.
Maybe Text
-> Maybe DiagnosticSeverity
-> a
-> Text
-> (a, ShowDiagnostic, Diagnostic)
ideErrorWithSource (Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"cradle") (DiagnosticSeverity -> Maybe DiagnosticSeverity
forall a. a -> Maybe a
Just DiagnosticSeverity
DsError) (String -> NormalizedFilePath
toNormalizedFilePath' String
fp) (String -> Text
T.pack (String -> Text) -> String -> Text
forall a b. (a -> b) -> a -> b
$ PackageSetupException -> String
showPackageSetupException PackageSetupException
e)