{-# LANGUAGE CPP #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
module Development.IDE.Session
(SessionLoadingOptions(..)
,CacheDirs(..)
,loadSession
,loadSessionWithOptions
,setInitialDynFlags
,getHieDbLoc
,runWithDb
,retryOnSqliteBusy
,retryOnException
,Log(..)
) where
import Control.Concurrent.Async
import Control.Concurrent.Strict
import Control.Exception.Safe as Safe
import Control.Monad
import Control.Monad.Extra
import Control.Monad.IO.Class
import qualified Crypto.Hash.SHA1 as H
import Data.Aeson hiding (Error)
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 Data.Hashable hiding (hash)
import qualified Data.HashMap.Strict as HM
import Data.List
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import qualified Data.Map.Strict as Map
import Data.Maybe
import Data.Proxy
import qualified Data.Text as T
import Data.Time.Clock
import Data.Version
import Development.IDE.Core.RuleTypes
import Development.IDE.Core.Shake hiding (Log, Priority,
knownTargets, withHieDb)
import qualified Development.IDE.GHC.Compat as Compat
import Development.IDE.GHC.Compat.Core hiding (Target,
TargetFile, TargetModule,
Var, Warning, getOptions)
import qualified Development.IDE.GHC.Compat.Core as GHC
import Development.IDE.GHC.Compat.Env hiding (Logger)
import Development.IDE.GHC.Compat.Units (UnitId)
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.Options
import GHC.Check
import qualified HIE.Bios as HieBios
import HIE.Bios.Environment hiding (getCacheDir)
import HIE.Bios.Types hiding (Log)
import qualified HIE.Bios.Types as HieBios
import Hie.Implicit.Cradle (loadImplicitHieCradle)
import Ide.Logger (Pretty (pretty),
Priority (Debug, Error, Info, Warning),
Recorder, WithPriority,
cmapWithPrio, logWith,
nest,
toCologActionWithPrio,
vcat, viaShow, (<+>))
import Language.LSP.Protocol.Message
import Language.LSP.Server
import System.Directory
import qualified System.Directory.Extra as IO
import System.FilePath
import System.Info
import Control.Applicative (Alternative ((<|>)))
import Data.Void
import Control.Concurrent.STM.Stats (atomically, modifyTVar',
readTVar, writeTVar)
import Control.Concurrent.STM.TQueue
import Control.DeepSeq
import Control.Exception (evaluate)
import Control.Monad.IO.Unlift (MonadUnliftIO)
import Data.Foldable (for_)
import Data.HashMap.Strict (HashMap)
import Data.HashSet (HashSet)
import qualified Data.HashSet as Set
import Database.SQLite.Simple
import Development.IDE.Core.Tracing (withTrace)
import Development.IDE.Session.Diagnostics (renderCradleError)
import Development.IDE.Types.Shake (WithHieDb)
import HieDb.Create
import HieDb.Types
import HieDb.Utils
import qualified System.Random as Random
import System.Random (RandomGen)
#if !MIN_VERSION_ghc(9,4,0)
import Data.IORef
#endif
data Log
= LogSettingInitialDynFlags
| LogGetInitialGhcLibDirDefaultCradleFail !CradleError !FilePath !(Maybe FilePath) !(Cradle Void)
| LogGetInitialGhcLibDirDefaultCradleNone
| LogHieDbRetry !Int !Int !Int !SomeException
| LogHieDbRetriesExhausted !Int !Int !Int !SomeException
| LogHieDbWriterThreadSQLiteError !SQLError
| LogHieDbWriterThreadException !SomeException
| LogInterfaceFilesCacheDir !FilePath
| LogKnownFilesUpdated !(HashMap Target (HashSet NormalizedFilePath))
| LogMakingNewHscEnv ![UnitId]
| LogDLLLoadError !String
| LogCradlePath !FilePath
| LogCradleNotFound !FilePath
| LogSessionLoadingResult !(Either [CradleError] (ComponentOptions, FilePath))
| LogCradle !(Cradle Void)
| LogNoneCradleFound FilePath
| LogNewComponentCache !(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
| LogHieBios HieBios.Log
deriving instance Show Log
instance Pretty Log where
pretty :: forall ann. Log -> Doc ann
pretty = \case
LogNoneCradleFound String
path ->
Doc ann
"None cradle found for" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
path forall ann. Doc ann -> Doc ann -> Doc ann
<+> Doc ann
", ignoring the file"
Log
LogSettingInitialDynFlags ->
Doc ann
"Setting initial dynflags..."
LogGetInitialGhcLibDirDefaultCradleFail CradleError
cradleError String
rootDirPath Maybe String
hieYamlPath Cradle Void
cradle ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Couldn't load cradle for ghc libdir."
, Doc ann
"Cradle error:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow CradleError
cradleError
, Doc ann
"Root dir path:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
rootDirPath
, Doc ann
"hie.yaml path:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Maybe String
hieYamlPath
, Doc ann
"Cradle:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Cradle Void
cradle ]
Log
LogGetInitialGhcLibDirDefaultCradleNone ->
Doc ann
"Couldn't load cradle. Cradle not found."
LogHieDbRetry Int
delay Int
maxDelay Int
retriesRemaining SomeException
e ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Retrying hiedb action..."
, Doc ann
"delay:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
delay
, Doc ann
"maximum delay:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
maxDelay
, Doc ann
"retries remaining:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
retriesRemaining
, Doc ann
"SQLite error:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty (forall e. Exception e => e -> String
displayException SomeException
e) ]
LogHieDbRetriesExhausted Int
baseDelay Int
maxDelay Int
retriesRemaining SomeException
e ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Retries exhausted for hiedb action."
, Doc ann
"base delay:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
baseDelay
, Doc ann
"maximum delay:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
maxDelay
, Doc ann
"retries remaining:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty Int
retriesRemaining
, Doc ann
"Exception:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty (forall e. Exception e => e -> String
displayException SomeException
e) ]
LogHieDbWriterThreadSQLiteError SQLError
e ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"HieDb writer thread SQLite error:"
, forall a ann. Pretty a => a -> Doc ann
pretty (forall e. Exception e => e -> String
displayException SQLError
e) ]
LogHieDbWriterThreadException SomeException
e ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"HieDb writer thread exception:"
, forall a ann. Pretty a => a -> Doc ann
pretty (forall e. Exception e => e -> String
displayException SomeException
e) ]
LogInterfaceFilesCacheDir String
path ->
Doc ann
"Interface files cache directory:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
path
LogKnownFilesUpdated HashMap Target (HashSet NormalizedFilePath)
targetToPathsMap ->
forall ann. Int -> Doc ann -> Doc ann
nest Int
2 forall a b. (a -> b) -> a -> b
$
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"Known files updated:"
, forall a ann. Show a => a -> Doc ann
viaShow forall a b. (a -> b) -> a -> b
$ (forall v1 v2 k. (v1 -> v2) -> HashMap k v1 -> HashMap k v2
HM.map forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall b a.
(Hashable b, Eq b) =>
(a -> b) -> HashSet a -> HashSet b
Set.map) NormalizedFilePath -> String
fromNormalizedFilePath HashMap Target (HashSet NormalizedFilePath)
targetToPathsMap
]
LogMakingNewHscEnv [UnitId]
inPlaceUnitIds ->
Doc ann
"Making new HscEnv. In-place unit ids:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty (forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [UnitId]
inPlaceUnitIds)
LogDLLLoadError String
errorString ->
Doc ann
"Error dynamically loading libm.so.6:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
errorString
LogCradlePath String
path ->
Doc ann
"Cradle path:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
path
LogCradleNotFound String
path ->
forall ann. [Doc ann] -> Doc ann
vcat
[ Doc ann
"No [cradle](https://github.com/mpickering/hie-bios#hie-bios) found for" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Pretty a => a -> Doc ann
pretty String
path forall a. Semigroup a => a -> a -> a
<> Doc ann
"."
, Doc ann
"Proceeding with [implicit cradle](https://hackage.haskell.org/package/implicit-hie)."
, Doc ann
"You should ignore this message, unless you see a 'Multi Cradle: No prefixes matched' error." ]
LogSessionLoadingResult Either [CradleError] (ComponentOptions, String)
e ->
Doc ann
"Session loading result:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Either [CradleError] (ComponentOptions, String)
e
LogCradle Cradle Void
cradle ->
Doc ann
"Cradle:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow Cradle Void
cradle
LogNewComponentCache (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
componentCache ->
Doc ann
"New component cache HscEnvEq:" forall ann. Doc ann -> Doc ann -> Doc ann
<+> forall a ann. Show a => a -> Doc ann
viaShow (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
componentCache
LogHieBios Log
msg -> forall a ann. Pretty a => a -> Doc ann
pretty Log
msg
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)
, SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
loadCradle :: Maybe FilePath -> FilePath -> IO (HieBios.Cradle Void)
, SessionLoadingOptions -> String -> [String] -> IO CacheDirs
getCacheDirs :: String -> [String] -> IO CacheDirs
, SessionLoadingOptions
-> Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getInitialGhcLibDir :: Recorder (WithPriority Log) -> FilePath -> IO (Maybe LibDir)
#if !MIN_VERSION_ghc(9,3,0)
, SessionLoadingOptions -> UnitId
fakeUid :: UnitId
#endif
}
instance Default SessionLoadingOptions where
def :: SessionLoadingOptions
def = 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 :: Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getInitialGhcLibDir = Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getInitialGhcLibDirDefault
#if !MIN_VERSION_ghc(9,3,0)
,fakeUid :: UnitId
fakeUid = Unit -> UnitId
Compat.toUnitId (String -> Unit
Compat.stringToUnit String
"main")
#endif
}
loadWithImplicitCradle :: Maybe FilePath
-> FilePath
-> 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 -> forall a. String -> IO (Cradle a)
loadImplicitHieCradle forall a b. (a -> b) -> a -> b
$ ShowS
addTrailingPathSeparator String
rootDir
getInitialGhcLibDirDefault :: Recorder (WithPriority Log) -> FilePath -> IO (Maybe LibDir)
getInitialGhcLibDirDefault :: Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getInitialGhcLibDirDefault Recorder (WithPriority Log)
recorder String
rootDir = do
Maybe String
hieYaml <- SessionLoadingOptions -> String -> IO (Maybe String)
findCradle forall a. Default a => a
def (String
rootDir String -> ShowS
</> String
"a")
Cradle Void
cradle <- SessionLoadingOptions -> Maybe String -> String -> IO (Cradle Void)
loadCradle forall a. Default a => a
def Maybe String
hieYaml String
rootDir
CradleLoadResult String
libDirRes <- forall a.
LogAction IO (WithSeverity Log)
-> Cradle a -> IO (CradleLoadResult String)
getRuntimeGhcLibDir (forall (m :: * -> *) msg.
(MonadIO m, HasCallStack) =>
Recorder (WithPriority msg) -> LogAction m (WithSeverity msg)
toCologActionWithPrio (forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogHieBios Recorder (WithPriority Log)
recorder)) Cradle Void
cradle
case CradleLoadResult String
libDirRes of
CradleSuccess String
libdir -> forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ String -> LibDir
LibDir String
libdir
CradleFail CradleError
err -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Error forall a b. (a -> b) -> a -> b
$ CradleError -> String -> Maybe String -> Cradle Void -> Log
LogGetInitialGhcLibDirDefaultCradleFail CradleError
err String
rootDir Maybe String
hieYaml Cradle Void
cradle
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
CradleLoadResult String
CradleNone -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning Log
LogGetInitialGhcLibDirDefaultCradleNone
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a. Maybe a
Nothing
setInitialDynFlags :: Recorder (WithPriority Log) -> FilePath -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags :: Recorder (WithPriority Log)
-> String -> SessionLoadingOptions -> IO (Maybe LibDir)
setInitialDynFlags Recorder (WithPriority Log)
recorder String
rootDir SessionLoadingOptions{UnitId
String -> IO (Maybe String)
String -> [String] -> IO CacheDirs
Maybe String -> String -> IO (Cradle Void)
Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
fakeUid :: UnitId
getInitialGhcLibDir :: Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getCacheDirs :: String -> [String] -> IO CacheDirs
loadCradle :: Maybe String -> String -> IO (Cradle Void)
findCradle :: String -> IO (Maybe String)
fakeUid :: SessionLoadingOptions -> UnitId
getInitialGhcLibDir :: SessionLoadingOptions
-> Recorder (WithPriority Log) -> 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 <- Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getInitialGhcLibDir Recorder (WithPriority Log)
recorder String
rootDir
Maybe DynFlags
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
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug Log
LogSettingInitialDynFlags
forall (t :: * -> *) (m :: * -> *) a b.
(Foldable t, Monad m) =>
(a -> m b) -> t a -> m ()
mapM_ DynFlags -> IO ()
setUnsafeGlobalDynFlags Maybe DynFlags
dynFlags
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe LibDir
libdir
retryOnException
:: (MonadIO m, MonadCatch m, RandomGen g, Exception e)
=> (e -> Maybe e)
-> Recorder (WithPriority Log)
-> Int
-> Int
-> Int
-> g
-> m a
-> m a
retryOnException :: forall (m :: * -> *) g e a.
(MonadIO m, MonadCatch m, RandomGen g, Exception e) =>
(e -> Maybe e)
-> Recorder (WithPriority Log)
-> Int
-> Int
-> Int
-> g
-> m a
-> m a
retryOnException e -> Maybe e
exceptionPred Recorder (WithPriority Log)
recorder Int
maxDelay !Int
baseDelay !Int
maxTimesRetry g
rng m a
action = do
Either e a
result <- forall (m :: * -> *) e b a.
(MonadCatch m, Exception e) =>
(e -> Maybe b) -> m a -> m (Either b a)
tryJust e -> Maybe e
exceptionPred m a
action
case Either e a
result of
Left e
e
| Int
maxTimesRetry forall a. Ord a => a -> a -> Bool
> Int
0 -> do
let newBaseDelay :: Int
newBaseDelay = forall a. Ord a => a -> a -> a
min Int
maxDelay (Int
baseDelay forall a. Num a => a -> a -> a
* Int
2)
let (Int
delay, g
newRng) = forall a g. (Random a, RandomGen g) => (a, a) -> g -> (a, g)
Random.randomR (Int
0, Int
newBaseDelay) g
rng
let newMaxTimesRetry :: Int
newMaxTimesRetry = Int
maxTimesRetry forall a. Num a => a -> a -> a
- Int
1
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> SomeException -> Log
LogHieDbRetry Int
delay Int
maxDelay Int
newMaxTimesRetry (forall e. Exception e => e -> SomeException
toException e
e)
Int -> IO ()
threadDelay Int
delay
forall (m :: * -> *) g e a.
(MonadIO m, MonadCatch m, RandomGen g, Exception e) =>
(e -> Maybe e)
-> Recorder (WithPriority Log)
-> Int
-> Int
-> Int
-> g
-> m a
-> m a
retryOnException e -> Maybe e
exceptionPred Recorder (WithPriority Log)
recorder Int
maxDelay Int
newBaseDelay Int
newMaxTimesRetry g
newRng m a
action
| Bool
otherwise -> do
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning forall a b. (a -> b) -> a -> b
$ Int -> Int -> Int -> SomeException -> Log
LogHieDbRetriesExhausted Int
baseDelay Int
maxDelay Int
maxTimesRetry (forall e. Exception e => e -> SomeException
toException e
e)
forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO e
e
Right a
b -> forall (f :: * -> *) a. Applicative f => a -> f a
pure a
b
oneSecond :: Int
oneSecond :: Int
oneSecond = Int
1000000
oneMillisecond :: Int
oneMillisecond :: Int
oneMillisecond = Int
1000
maxRetryCount :: Int
maxRetryCount :: Int
maxRetryCount = Int
10
retryOnSqliteBusy :: (MonadIO m, MonadCatch m, RandomGen g)
=> Recorder (WithPriority Log) -> g -> m a -> m a
retryOnSqliteBusy :: forall (m :: * -> *) g a.
(MonadIO m, MonadCatch m, RandomGen g) =>
Recorder (WithPriority Log) -> g -> m a -> m a
retryOnSqliteBusy Recorder (WithPriority Log)
recorder g
rng m a
action =
let isErrorBusy :: SQLError -> Maybe SQLError
isErrorBusy SQLError
e
| SQLError{ sqlError :: SQLError -> Error
sqlError = Error
ErrorBusy } <- SQLError
e = forall a. a -> Maybe a
Just SQLError
e
| Bool
otherwise = forall a. Maybe a
Nothing
in
forall (m :: * -> *) g e a.
(MonadIO m, MonadCatch m, RandomGen g, Exception e) =>
(e -> Maybe e)
-> Recorder (WithPriority Log)
-> Int
-> Int
-> Int
-> g
-> m a
-> m a
retryOnException SQLError -> Maybe SQLError
isErrorBusy Recorder (WithPriority Log)
recorder Int
oneSecond Int
oneMillisecond Int
maxRetryCount g
rng m a
action
makeWithHieDbRetryable :: RandomGen g => Recorder (WithPriority Log) -> g -> HieDb -> WithHieDb
makeWithHieDbRetryable :: forall g.
RandomGen g =>
Recorder (WithPriority Log) -> g -> HieDb -> WithHieDb
makeWithHieDbRetryable Recorder (WithPriority Log)
recorder g
rng HieDb
hieDb HieDb -> IO a
f =
forall (m :: * -> *) g a.
(MonadIO m, MonadCatch m, RandomGen g) =>
Recorder (WithPriority Log) -> g -> m a -> m a
retryOnSqliteBusy Recorder (WithPriority Log)
recorder g
rng (HieDb -> IO a
f HieDb
hieDb)
runWithDb :: Recorder (WithPriority Log) -> FilePath -> (WithHieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb :: Recorder (WithPriority Log)
-> String -> (WithHieDb -> IndexQueue -> IO ()) -> IO ()
runWithDb Recorder (WithPriority Log)
recorder String
fp WithHieDb -> IndexQueue -> IO ()
k = do
StdGen
rng <- forall (m :: * -> *). MonadIO m => m StdGen
Random.newStdGen
forall (m :: * -> *) g a.
(MonadIO m, MonadCatch m, RandomGen g) =>
Recorder (WithPriority Log) -> g -> m a -> m a
retryOnSqliteBusy
Recorder (WithPriority Log)
recorder
StdGen
rng
(forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp (forall a b. a -> b -> a
const forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Applicative f => a -> f a
pure ()) forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`Safe.catch` \IncompatibleSchemaVersion{} -> String -> IO ()
removeFile String
fp)
forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp forall a b. (a -> b) -> a -> b
$ \HieDb
writedb -> do
let withWriteDbRetryable :: WithHieDb
withWriteDbRetryable :: WithHieDb
withWriteDbRetryable = forall g.
RandomGen g =>
Recorder (WithPriority Log) -> g -> HieDb -> WithHieDb
makeWithHieDbRetryable Recorder (WithPriority Log)
recorder StdGen
rng HieDb
writedb
WithHieDb
withWriteDbRetryable HieDb -> IO ()
initConn
IndexQueue
chan <- forall a. IO (TQueue a)
newTQueueIO
forall a b. IO a -> (Async a -> IO b) -> IO b
withAsync (WithHieDb -> IndexQueue -> IO ()
writerThread WithHieDb
withWriteDbRetryable IndexQueue
chan) forall a b. (a -> b) -> a -> b
$ \Async ()
_ -> do
forall a. String -> (HieDb -> IO a) -> IO a
withHieDb String
fp (\HieDb
readDb -> WithHieDb -> IndexQueue -> IO ()
k (forall g.
RandomGen g =>
Recorder (WithPriority Log) -> g -> HieDb -> WithHieDb
makeWithHieDbRetryable Recorder (WithPriority Log)
recorder StdGen
rng HieDb
readDb) IndexQueue
chan)
where
writerThread :: WithHieDb -> IndexQueue -> IO ()
writerThread :: WithHieDb -> IndexQueue -> IO ()
writerThread WithHieDb
withHieDbRetryable IndexQueue
chan = do
()
_ <- WithHieDb
withHieDbRetryable HieDb -> IO ()
deleteMissingRealFiles
Int
_ <- WithHieDb
withHieDbRetryable HieDb -> IO Int
garbageCollectTypeNames
forall (f :: * -> *) a b. Applicative f => f a -> f b
forever forall a b. (a -> b) -> a -> b
$ do
((HieDb -> IO ()) -> IO ()) -> IO ()
l <- forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TQueue a -> STM a
readTQueue IndexQueue
chan
((HieDb -> IO ()) -> IO ()) -> IO ()
l WithHieDb
withHieDbRetryable
forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`Safe.catch` \e :: SQLError
e@SQLError{} -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Error forall a b. (a -> b) -> a -> b
$ SQLError -> Log
LogHieDbWriterThreadSQLiteError SQLError
e
forall (m :: * -> *) a.
MonadCatch m =>
m a -> (SomeException -> m a) -> m a
`Safe.catchAny` \SomeException
f -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Error forall a b. (a -> b) -> a -> b
$ SomeException -> Log
LogHieDbWriterThreadException SomeException
f
getHieDbLoc :: FilePath -> IO FilePath
getHieDbLoc :: String -> IO String
getHieDbLoc String
dir = do
let db :: String
db = forall a. [a] -> [[a]] -> [a]
intercalate String
"-" [String
dirHash, ShowS
takeBaseName String
dir, String
Compat.ghcVersionStr, String
hiedbDataVersion] String -> ShowS
<.> String
"hiedb"
dirHash :: String
dirHash = ByteString -> String
B.unpack forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
B16.encode forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
H.hash 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
forall (f :: * -> *) a. Applicative f => a -> f a
pure (String
cDir String -> ShowS
</> String
db)
loadSession :: Recorder (WithPriority Log) -> FilePath -> IO (Action IdeGhcSession)
loadSession :: Recorder (WithPriority Log) -> String -> IO (Action IdeGhcSession)
loadSession Recorder (WithPriority Log)
recorder = Recorder (WithPriority Log)
-> SessionLoadingOptions -> String -> IO (Action IdeGhcSession)
loadSessionWithOptions Recorder (WithPriority Log)
recorder forall a. Default a => a
def
loadSessionWithOptions :: Recorder (WithPriority Log) -> SessionLoadingOptions -> FilePath -> IO (Action IdeGhcSession)
loadSessionWithOptions :: Recorder (WithPriority Log)
-> SessionLoadingOptions -> String -> IO (Action IdeGhcSession)
loadSessionWithOptions Recorder (WithPriority Log)
recorder SessionLoadingOptions{UnitId
String -> IO (Maybe String)
String -> [String] -> IO CacheDirs
Maybe String -> String -> IO (Cradle Void)
Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
fakeUid :: UnitId
getInitialGhcLibDir :: Recorder (WithPriority Log) -> String -> IO (Maybe LibDir)
getCacheDirs :: String -> [String] -> IO CacheDirs
loadCradle :: Maybe String -> String -> IO (Cradle Void)
findCradle :: String -> IO (Maybe String)
fakeUid :: SessionLoadingOptions -> UnitId
getInitialGhcLibDir :: SessionLoadingOptions
-> Recorder (WithPriority Log) -> 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
Var HieMap
hscEnvs <- forall a. a -> IO (Var a)
newVar forall k a. Map k a
Map.empty :: IO (Var HieMap)
Var FlagsMap
fileToFlags <- forall a. a -> IO (Var a)
newVar forall k a. Map k a
Map.empty :: IO (Var FlagsMap)
Var FilesMap
filesMap <- forall a. a -> IO (Var a)
newVar forall k v. HashMap k v
HM.empty :: IO (Var FilesMap)
Var Int
version <- forall a. a -> IO (Var a)
newVar Int
0
let returnWithVersion :: (String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String]))
-> Action IdeGhcSession
returnWithVersion String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
fun = (String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String]))
-> Int -> IdeGhcSession
IdeGhcSession String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
fun forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. Var a -> IO a
readVar Var Int
version)
String -> IO (Maybe String)
cradleLoc <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a b. Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO forall a b. (a -> b) -> a -> b
$ \String
v -> do
Maybe String
res <- String -> IO (Maybe String)
findCradle String
v
Maybe String
res' <- 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
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ ShowS
normalise forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe String
res'
Async (([FileDiagnostic], Maybe HscEnvEq), [String])
dummyAs <- forall a. IO a -> IO (Async a)
async forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => a -> m a
return (forall a. HasCallStack => String -> a
error String
"Uninitialised")
Var (Async (([FileDiagnostic], Maybe HscEnvEq), [String]))
runningCradle <- forall a. a -> IO (Var a)
newVar Async (([FileDiagnostic], Maybe HscEnvEq), [String])
dummyAs :: IO (Var (Async (IdeResult HscEnvEq,[FilePath])))
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ do
extras :: ShakeExtras
extras@ShakeExtras{VFSModified -> String -> [DelayedAction ()] -> IO ()
$sel:restartShakeSession:ShakeExtras :: ShakeExtras -> VFSModified -> String -> [DelayedAction ()] -> IO ()
restartShakeSession :: VFSModified -> String -> [DelayedAction ()] -> IO ()
restartShakeSession, IORef NameCache
$sel:ideNc:ShakeExtras :: ShakeExtras -> IORef NameCache
ideNc :: IORef NameCache
ideNc, TVar (Hashed (HashMap Target (HashSet NormalizedFilePath)))
$sel:knownTargetsVar:ShakeExtras :: ShakeExtras
-> TVar (Hashed (HashMap Target (HashSet NormalizedFilePath)))
knownTargetsVar :: TVar (Hashed (HashMap Target (HashSet NormalizedFilePath)))
knownTargetsVar, Maybe (LanguageContextEnv Config)
$sel:lspEnv:ShakeExtras :: ShakeExtras -> Maybe (LanguageContextEnv Config)
lspEnv :: Maybe (LanguageContextEnv Config)
lspEnv
} <- Action ShakeExtras
getShakeExtras
let invalidateShakeCache :: IO ()
invalidateShakeCache :: IO ()
invalidateShakeCache = do
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Var a -> (a -> a) -> IO a
modifyVar' Var Int
version forall a. Enum a => a -> a
succ
forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys ShakeExtras
extras GhcSessionIO
GhcSessionIO [NormalizedFilePath
emptyFilePath]
IdeOptions{ optTesting :: IdeOptions -> IdeTesting
optTesting = IdeTesting Bool
optTesting
, optCheckProject :: IdeOptions -> IO Bool
optCheckProject = IO Bool
getCheckProject
, [String]
optExtensions :: IdeOptions -> [String]
optExtensions :: [String]
optExtensions
} <- Action IdeOptions
getIdeOptions
let extendKnownTargets :: [TargetDetails] -> IO ()
extendKnownTargets [TargetDetails]
newTargets = do
[(Target, [NormalizedFilePath])]
knownTargets <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM [TargetDetails]
newTargets forall a b. (a -> b) -> a -> b
$ \TargetDetails{[NormalizedFilePath]
([FileDiagnostic], Maybe HscEnvEq)
DependencyInfo
Target
targetLocations :: TargetDetails -> [NormalizedFilePath]
targetDepends :: TargetDetails -> DependencyInfo
targetEnv :: TargetDetails -> ([FileDiagnostic], Maybe HscEnvEq)
targetTarget :: TargetDetails -> Target
targetLocations :: [NormalizedFilePath]
targetDepends :: DependencyInfo
targetEnv :: ([FileDiagnostic], Maybe HscEnvEq)
targetTarget :: Target
..} ->
case Target
targetTarget of
TargetFile NormalizedFilePath
f -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (Target
targetTarget, [NormalizedFilePath
f])
TargetModule ModuleName
_ -> do
[NormalizedFilePath]
found <- forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesFileExist forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath -> String
fromNormalizedFilePath) [NormalizedFilePath]
targetLocations
forall (m :: * -> *) a. Monad m => a -> m a
return (Target
targetTarget, [NormalizedFilePath]
found)
Maybe (HashMap Target (HashSet NormalizedFilePath))
hasUpdate <- forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ do
Hashed (HashMap Target (HashSet NormalizedFilePath))
known <- forall a. TVar a -> STM a
readTVar TVar (Hashed (HashMap Target (HashSet NormalizedFilePath)))
knownTargetsVar
let known' :: Hashed (HashMap Target (HashSet NormalizedFilePath))
known' = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall b a. Hashable b => (a -> b) -> Hashed a -> Hashed b
mapHashed Hashed (HashMap Target (HashSet NormalizedFilePath))
known forall a b. (a -> b) -> a -> b
$ \HashMap Target (HashSet NormalizedFilePath)
k ->
forall k v.
(Eq k, Hashable k) =>
(v -> v -> v) -> HashMap k v -> HashMap k v -> HashMap k v
HM.unionWith forall a. Semigroup a => a -> a -> a
(<>) HashMap Target (HashSet NormalizedFilePath)
k forall a b. (a -> b) -> a -> b
$ forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second forall a. (Eq a, Hashable a) => [a] -> HashSet a
Set.fromList) [(Target, [NormalizedFilePath])]
knownTargets
hasUpdate :: Maybe (HashMap Target (HashSet NormalizedFilePath))
hasUpdate = if Hashed (HashMap Target (HashSet NormalizedFilePath))
known forall a. Eq a => a -> a -> Bool
/= Hashed (HashMap Target (HashSet NormalizedFilePath))
known' then forall a. a -> Maybe a
Just (forall a. Hashed a -> a
unhashed Hashed (HashMap Target (HashSet NormalizedFilePath))
known') else forall a. Maybe a
Nothing
forall a. TVar a -> a -> STM ()
writeTVar TVar (Hashed (HashMap Target (HashSet NormalizedFilePath)))
knownTargetsVar Hashed (HashMap Target (HashSet NormalizedFilePath))
known'
IO ()
logDirtyKeys <- forall k.
ShakeValue k =>
ShakeExtras -> k -> [NormalizedFilePath] -> STM (IO ())
recordDirtyKeys ShakeExtras
extras GetKnownTargets
GetKnownTargets [NormalizedFilePath
emptyFilePath]
forall (m :: * -> *) a. Monad m => a -> m a
return (IO ()
logDirtyKeys forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe (HashMap Target (HashSet NormalizedFilePath))
hasUpdate)
forall (t :: * -> *) (f :: * -> *) a b.
(Foldable t, Applicative f) =>
t a -> (a -> f b) -> f ()
for_ Maybe (HashMap Target (HashSet NormalizedFilePath))
hasUpdate forall a b. (a -> b) -> a -> b
$ \HashMap Target (HashSet NormalizedFilePath)
x ->
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug forall a b. (a -> b) -> a -> b
$ HashMap Target (HashSet NormalizedFilePath) -> Log
LogKnownFilesUpdated HashMap Target (HashSet NormalizedFilePath)
x
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
HscEnv
hscEnv <- IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
ideNc String
libDir
(DynFlags
df', [Target]
targets) <- forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hscEnv forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *).
GhcMonad m =>
ComponentOptions -> DynFlags -> m (DynFlags, [Target])
setOptions ComponentOptions
opts (HscEnv -> DynFlags
hsc_dflags HscEnv
hscEnv)
let df :: DynFlags
df =
#if MIN_VERSION_ghc(9,3,0)
case unitIdString (homeUnitId_ df') of
"main" ->
let hash = B.unpack $ B16.encode $ H.finalize $ H.updates H.init (map B.pack $ componentOptions opts)
hashed_uid = Compat.toUnitId (Compat.stringToUnit ("main-"++hash))
in setHomeUnitId_ hashed_uid df'
_ -> df'
#else
DynFlags
df'
#endif
let deps :: [String]
deps = ComponentOptions -> [String]
componentDependencies ComponentOptions
opts forall a. [a] -> [a] -> [a]
++ forall a. Maybe a -> [a]
maybeToList Maybe String
hieYaml
DependencyInfo
dep_info <- [String] -> IO DependencyInfo
getDependencyInfo [String]
deps
forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var HieMap
hscEnvs forall a b. (a -> b) -> a -> b
$ \HieMap
m -> do
let oldDeps :: Maybe (HscEnv, [RawComponentInfo])
oldDeps = forall k a. Ord k => k -> Map k a -> Maybe a
Map.lookup Maybe String
hieYaml HieMap
m
let
new_deps :: NonEmpty RawComponentInfo
new_deps = UnitId
-> DynFlags
-> [Target]
-> NormalizedFilePath
-> ComponentOptions
-> DependencyInfo
-> RawComponentInfo
RawComponentInfo (DynFlags -> UnitId
homeUnitId_ DynFlags
df) DynFlags
df [Target]
targets NormalizedFilePath
cfp ComponentOptions
opts DependencyInfo
dep_info
forall a. a -> [a] -> NonEmpty a
:| forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall a b. (a, b) -> b
snd Maybe (HscEnv, [RawComponentInfo])
oldDeps
inplace :: [UnitId]
inplace = forall a b. (a -> b) -> [a] -> [b]
map RawComponentInfo -> UnitId
rawComponentUnitId forall a b. (a -> b) -> a -> b
$ forall a. NonEmpty a -> [a]
NE.toList NonEmpty RawComponentInfo
new_deps
NonEmpty ComponentInfo
new_deps' <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
t a -> (a -> m b) -> m (t b)
forM NonEmpty RawComponentInfo
new_deps forall a b. (a -> b) -> a -> b
$ \RawComponentInfo{[Target]
DependencyInfo
DynFlags
UnitId
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 :: UnitId
rawComponentUnitId :: RawComponentInfo -> UnitId
..} -> do
#if MIN_VERSION_ghc(9,3,0)
let (df2, uids) = (rawComponentDynFlags, [])
#else
let (DynFlags
df2, [UnitId]
uids) = UnitId -> [UnitId] -> DynFlags -> (DynFlags, [UnitId])
_removeInplacePackages UnitId
fakeUid [UnitId]
inplace DynFlags
rawComponentDynFlags
#endif
let prefix :: String
prefix = forall a. Show a => a -> String
show UnitId
rawComponentUnitId
let hscComponents :: [String]
hscComponents = forall a. Ord a => [a] -> [a]
sort forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a. Show a => a -> String
show [UnitId]
uids
cacheDirOpts :: [String]
cacheDirOpts = [String]
hscComponents forall a. [a] -> [a] -> [a]
++ ComponentOptions -> [String]
componentOptions ComponentOptions
opts
CacheDirs
cacheDirs <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ String -> [String] -> IO CacheDirs
getCacheDirs String
prefix [String]
cacheDirOpts
DynFlags
processed_df <- forall (m :: * -> *).
MonadUnliftIO m =>
Recorder (WithPriority Log) -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs Recorder (WithPriority Log)
recorder CacheDirs
cacheDirs DynFlags
df2
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ UnitId
-> DynFlags
-> [UnitId]
-> [Target]
-> NormalizedFilePath
-> ComponentOptions
-> DependencyInfo
-> ComponentInfo
ComponentInfo UnitId
rawComponentUnitId
DynFlags
processed_df
[UnitId]
uids
[Target]
rawComponentTargets
NormalizedFilePath
rawComponentFP
ComponentOptions
rawComponentCOptions
DependencyInfo
rawComponentDependencyInfo
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info forall a b. (a -> b) -> a -> b
$ [UnitId] -> Log
LogMakingNewHscEnv [UnitId]
inplace
HscEnv
hscEnvB <- IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
ideNc String
libDir
!HscEnv
newHscEnv <-
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hscEnvB forall a b. (a -> b) -> a -> b
$ do
()
_ <- forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setSessionDynFlags
#if !MIN_VERSION_ghc(9,3,0)
forall a b. (a -> b) -> a -> b
$ UnitId -> DynFlags -> DynFlags
setHomeUnitId_ UnitId
fakeUid
#endif
DynFlags
df
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Maybe String
hieYaml (HscEnv
newHscEnv, forall a. NonEmpty a -> [a]
NE.toList NonEmpty RawComponentInfo
new_deps) HieMap
m, (HscEnv
newHscEnv, forall a. NonEmpty a -> a
NE.head NonEmpty ComponentInfo
new_deps', forall a. NonEmpty a -> [a]
NE.tail NonEmpty ComponentInfo
new_deps'))
let session :: (Maybe FilePath, NormalizedFilePath, ComponentOptions, FilePath)
-> IO (IdeResult HscEnvEq,[FilePath])
session :: (Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (([FileDiagnostic], Maybe 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
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
os forall a. Eq a => a -> a -> Bool
== String
"linux") 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 -> forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
Just String
err -> forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Error forall a b. (a -> b) -> a -> b
$ String -> Log
LogDLLLoadError String
err
let uids :: [(UnitId, DynFlags)]
uids = forall a b. (a -> b) -> [a] -> [b]
map (\ComponentInfo
ci -> (ComponentInfo -> UnitId
componentUnitId ComponentInfo
ci, ComponentInfo -> DynFlags
componentDynFlags ComponentInfo
ci)) (ComponentInfo
new forall a. a -> [a] -> [a]
: [ComponentInfo]
old_deps)
let new_cache :: ComponentInfo
-> IO
([TargetDetails],
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))
new_cache = Recorder (WithPriority Log)
-> [String]
-> Maybe String
-> NormalizedFilePath
-> HscEnv
-> [(UnitId, DynFlags)]
-> ComponentInfo
-> IO
([TargetDetails],
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))
newComponentCache Recorder (WithPriority Log)
recorder [String]
optExtensions Maybe String
hieYaml NormalizedFilePath
_cfp HscEnv
hscEnv [(UnitId, DynFlags)]
uids
([TargetDetails]
cs, (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
res) <- ComponentInfo
-> IO
([TargetDetails],
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))
new_cache ComponentInfo
new
[TargetDetails]
cached_targets <- forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. ComponentInfo
-> IO
([TargetDetails],
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))
new_cache) [ComponentInfo]
old_deps
let all_targets :: [TargetDetails]
all_targets = [TargetDetails]
cs forall a. [a] -> [a] -> [a]
++ [TargetDetails]
cached_targets
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FlagsMap
fileToFlags forall a b. (a -> b) -> a -> b
$
forall k a. Ord k => k -> a -> Map k a -> Map k a
Map.insert Maybe String
hieYaml (forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails
-> [(NormalizedFilePath,
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))]
toFlagsMap [TargetDetails]
all_targets))
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FilesMap
filesMap forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> b -> a -> c
flip forall k v.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k v -> HashMap k v
HM.union (forall k v. (Eq k, Hashable k) => [(k, v)] -> HashMap k v
HM.fromList (forall a b. [a] -> [b] -> [(a, b)]
zip (forall a b. (a -> b) -> [a] -> [b]
map forall a b. (a, b) -> a
fst forall a b. (a -> b) -> a -> b
$ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails
-> [(NormalizedFilePath,
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))]
toFlagsMap [TargetDetails]
all_targets) (forall a. a -> [a]
repeat Maybe String
hieYaml)))
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ [TargetDetails] -> IO ()
extendKnownTargets [TargetDetails]
all_targets
IO ()
invalidateShakeCache
VFSModified -> String -> [DelayedAction ()] -> IO ()
restartShakeSession VFSModified
VFSUnmodified String
"new component" []
Bool
checkProject <- IO Bool
getCheckProject
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
unless (forall (t :: * -> *) a. Foldable t => t a -> Bool
null [TargetDetails]
cs Bool -> Bool -> Bool
|| Bool -> Bool
not Bool
checkProject) forall a b. (a -> b) -> a -> b
$ do
[NormalizedFilePath]
cfps' <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a.
Applicative m =>
(a -> m Bool) -> [a] -> m [a]
filterM (String -> IO Bool
IO.doesFileExist forall b c a. (b -> c) -> (a -> b) -> a -> c
. NormalizedFilePath -> String
fromNormalizedFilePath) (forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap TargetDetails -> [NormalizedFilePath]
targetLocations [TargetDetails]
cs)
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. ShakeExtras -> DelayedAction a -> IO (IO a)
shakeEnqueue ShakeExtras
extras forall a b. (a -> b) -> a -> b
$ forall a. String -> Priority -> Action a -> DelayedAction a
mkDelayedAction String
"InitialLoad" Priority
Debug forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ do
[Maybe FileVersion]
mmt <- forall (f :: * -> *) k v.
(Traversable f, IdeRule k v) =>
k -> f NormalizedFilePath -> Action (f (Maybe v))
uses GetModificationTime
GetModificationTime [NormalizedFilePath]
cfps'
let cs_exist :: [NormalizedFilePath]
cs_exist = forall a. [Maybe a] -> [a]
catMaybes (forall a b c. (a -> b -> c) -> [a] -> [b] -> [c]
zipWith forall (f :: * -> *) a b. Functor f => a -> f b -> f a
(<$) [NormalizedFilePath]
cfps' [Maybe FileVersion]
mmt)
[Maybe HiFileResult]
modIfaces <- forall (f :: * -> *) k v.
(Traversable f, IdeRule k v) =>
k -> f NormalizedFilePath -> Action (f (Maybe v))
uses GetModIface
GetModIface [NormalizedFilePath]
cs_exist
ShakeExtras
shakeExtras <- Action ShakeExtras
getShakeExtras
let !exportsMap' :: ExportsMap
exportsMap' = [ModIface] -> ExportsMap
createExportsMap forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap HiFileResult -> ModIface
hirModIface) [Maybe HiFileResult]
modIfaces
forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. STM a -> IO a
atomically forall a b. (a -> b) -> a -> b
$ forall a. TVar a -> (a -> a) -> STM ()
modifyTVar' (ShakeExtras -> TVar ExportsMap
exportsMap ShakeExtras
shakeExtras) (ExportsMap
exportsMap' forall a. Semigroup a => a -> a -> a
<>)
forall (m :: * -> *) a. Monad m => a -> m a
return (forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second forall k a. Map k a -> [k]
Map.keys (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
res)
let consultCradle :: Maybe FilePath -> FilePath -> IO (IdeResult HscEnvEq, [FilePath])
consultCradle :: Maybe String
-> String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
consultCradle Maybe String
hieYaml String
cfp = do
String
lfpLog <- forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> ShowS
makeRelative String
cfp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getCurrentDirectory
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info forall a b. (a -> b) -> a -> b
$ String -> Log
LogCradlePath String
lfpLog
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (forall a. Maybe a -> Bool
isNothing Maybe String
hieYaml) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Warning forall a b. (a -> b) -> a -> b
$ String -> Log
LogCradleNotFound String
lfpLog
Cradle Void
cradle <- Maybe String -> String -> IO (Cradle Void)
loadCradle Maybe String
hieYaml String
dir
String
lfp <- forall a b c. (a -> b -> c) -> b -> a -> c
flip String -> ShowS
makeRelative String
cfp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IO String
getCurrentDirectory
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
optTesting forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) c.
Applicative m =>
Maybe (LanguageContextEnv c) -> LspT c m () -> m ()
mRunLspT Maybe (LanguageContextEnv Config)
lspEnv forall a b. (a -> b) -> a -> b
$
forall (m :: Method 'ServerToClient 'Notification) (f :: * -> *)
config.
MonadLsp config f =>
SServerMethod m -> MessageParams m -> f ()
sendNotification (forall {f :: MessageDirection} {t :: MessageKind} (s :: Symbol).
KnownSymbol s =>
Proxy s -> SMethod ('Method_CustomMethod s)
SMethod_CustomMethod (forall {k} (t :: k). Proxy t
Proxy @"ghcide/cradle/loaded")) (forall a. ToJSON a => a -> Value
toJSON String
cfp)
let progMsg :: Text
progMsg = Text
"Setting up " forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack (ShowS
takeBaseName (forall a. Cradle a -> String
cradleRootDir Cradle Void
cradle))
forall a. Semigroup a => a -> a -> a
<> Text
" (for " forall a. Semigroup a => a -> a -> a
<> String -> Text
T.pack String
lfp forall a. Semigroup a => a -> a -> a
<> Text
")"
Either [CradleError] (ComponentOptions, String)
eopts <- 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 (forall c (m :: * -> *) a.
MonadLsp c m =>
Text -> ProgressCancellable -> m a -> m a
withIndefiniteProgress Text
progMsg ProgressCancellable
NotCancellable) forall a b. (a -> b) -> a -> b
$
forall (m :: * -> *) a.
(MonadMask m, MonadIO m) =>
String -> ((String -> String -> m ()) -> m a) -> m a
withTrace String
"Load cradle" forall a b. (a -> b) -> a -> b
$ \String -> String -> IO ()
addTag -> do
String -> String -> IO ()
addTag String
"file" String
lfp
Either [CradleError] (ComponentOptions, String)
res <- Recorder (WithPriority Log)
-> Cradle Void
-> String
-> IO (Either [CradleError] (ComponentOptions, String))
cradleToOptsAndLibDir Recorder (WithPriority Log)
recorder Cradle Void
cradle String
cfp
String -> String -> IO ()
addTag String
"result" (forall a. Show a => a -> String
show Either [CradleError] (ComponentOptions, String)
res)
forall (m :: * -> *) a. Monad m => a -> m a
return Either [CradleError] (ComponentOptions, String)
res
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug forall a b. (a -> b) -> a -> b
$ Either [CradleError] (ComponentOptions, String) -> Log
LogSessionLoadingResult Either [CradleError] (ComponentOptions, String)
eopts
case Either [CradleError] (ComponentOptions, String)
eopts of
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
..} ->
forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"GHC installation not found in libdir: " 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
..} ->
forall (m :: * -> *) a. Monad m => a -> m a
return (([String -> PackageSetupException -> FileDiagnostic
renderPackageSetupException String
cfp GhcVersionMismatch{Version
runTime :: Version
compileTime :: Version
runTime :: Version
compileTime :: Version
..}], forall a. Maybe a
Nothing),[])
InstallationChecked Version
_compileTime Ghc PackageCheckResult
_ghcLibCheck ->
(Maybe String, NormalizedFilePath, ComponentOptions, String)
-> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
session (Maybe String
hieYaml, String -> NormalizedFilePath
toNormalizedFilePath' String
cfp, ComponentOptions
opts, String
libDir)
Left [CradleError]
err -> do
DependencyInfo
dep_info <- [String] -> IO DependencyInfo
getDependencyInfo (forall a. Maybe a -> [a]
maybeToList Maybe String
hieYaml)
let ncfp :: NormalizedFilePath
ncfp = String -> NormalizedFilePath
toNormalizedFilePath' String
cfp
let res :: ([FileDiagnostic], Maybe HscEnvEq)
res = (forall a b. (a -> b) -> [a] -> [b]
map (\CradleError
err' -> forall a.
CradleError -> Cradle a -> NormalizedFilePath -> FileDiagnostic
renderCradleError CradleError
err' Cradle Void
cradle NormalizedFilePath
ncfp) [CradleError]
err, forall a. Maybe a
Nothing)
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FlagsMap
fileToFlags forall a b. (a -> b) -> a -> b
$
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Map.insertWith forall k v.
(Eq k, Hashable k) =>
HashMap k v -> HashMap k v -> HashMap k v
HM.union Maybe String
hieYaml (forall k v. Hashable k => k -> v -> HashMap k v
HM.singleton NormalizedFilePath
ncfp (([FileDiagnostic], Maybe HscEnvEq)
res, DependencyInfo
dep_info))
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Var a -> (a -> a) -> IO a
modifyVar' Var FilesMap
filesMap forall a b. (a -> b) -> a -> b
$ forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
HM.insert NormalizedFilePath
ncfp Maybe String
hieYaml
forall (m :: * -> *) a. Monad m => a -> m a
return (([FileDiagnostic], Maybe HscEnvEq)
res, forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
hieYaml forall a. [a] -> [a] -> [a]
++ forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap CradleError -> [String]
cradleErrorDependencies [CradleError]
err)
let sessionOpts :: (Maybe FilePath, FilePath)
-> IO (IdeResult HscEnvEq, [FilePath])
sessionOpts :: (Maybe String, String)
-> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
sessionOpts (Maybe String
hieYaml, String
file) = do
HashMap
NormalizedFilePath
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
v <- forall k a. Ord k => a -> k -> Map k a -> a
Map.findWithDefault forall k v. HashMap k v
HM.empty Maybe String
hieYaml forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Var a -> IO a
readVar Var FlagsMap
fileToFlags
String
cfp <- String -> IO String
makeAbsolute String
file
case forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup (String -> NormalizedFilePath
toNormalizedFilePath' String
cfp) HashMap
NormalizedFilePath
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
v of
Just (([FileDiagnostic], Maybe 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
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ Var FlagsMap
fileToFlags (forall a b. a -> b -> a
const (forall (m :: * -> *) a. Monad m => a -> m a
return forall k a. Map k a
Map.empty))
forall a. Var a -> (a -> IO a) -> IO ()
modifyVar_ Var HieMap
hscEnvs (forall (m :: * -> *) a. Monad m => a -> m a
return forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 (([FileDiagnostic], Maybe HscEnvEq), [String])
consultCradle Maybe String
hieYaml String
cfp
else forall (m :: * -> *) a. Monad m => a -> m a
return (([FileDiagnostic], Maybe HscEnvEq)
opts, forall k a. Map k a -> [k]
Map.keys DependencyInfo
old_di)
Maybe (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
Nothing -> Maybe String
-> String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
consultCradle Maybe String
hieYaml String
cfp
let getOptions :: FilePath -> IO (IdeResult HscEnvEq, [FilePath])
getOptions :: String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
getOptions String
file = do
NormalizedFilePath
ncfp <- String -> NormalizedFilePath
toNormalizedFilePath' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
makeAbsolute String
file
Maybe (Maybe String)
cachedHieYamlLocation <- forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
HM.lookup NormalizedFilePath
ncfp forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Var a -> IO a
readVar Var FilesMap
filesMap
Maybe String
hieYaml <- String -> IO (Maybe String)
cradleLoc String
file
(Maybe String, String)
-> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
sessionOpts (forall (m :: * -> *) a. Monad m => m (m a) -> m a
join Maybe (Maybe String)
cachedHieYamlLocation forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> Maybe String
hieYaml, String
file) forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> (e -> m a) -> m a
`Safe.catch` \PackageSetupException
e ->
forall (m :: * -> *) a. Monad m => a -> m a
return (([String -> PackageSetupException -> FileDiagnostic
renderPackageSetupException String
file PackageSetupException
e], forall a. Maybe a
Nothing), forall b a. b -> (a -> b) -> Maybe a -> b
maybe [] forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe String
hieYaml)
(String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String]))
-> Action IdeGhcSession
returnWithVersion forall a b. (a -> b) -> a -> b
$ \String
file -> do
(([FileDiagnostic], Maybe HscEnvEq), [String])
opts <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ forall a b. (a -> b) -> a -> b
$ forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var (Async (([FileDiagnostic], Maybe HscEnvEq), [String]))
runningCradle forall a b. (a -> b) -> a -> b
$ \Async (([FileDiagnostic], Maybe HscEnvEq), [String])
as -> do
forall (f :: * -> *) a. Functor f => f a -> f ()
void forall a b. (a -> b) -> a -> b
$ forall a. Async a -> IO a
wait Async (([FileDiagnostic], Maybe HscEnvEq), [String])
as
Async (([FileDiagnostic], Maybe HscEnvEq), [String])
asyncRes <- forall a. IO a -> IO (Async a)
async forall a b. (a -> b) -> a -> b
$ String -> IO (([FileDiagnostic], Maybe HscEnvEq), [String])
getOptions String
file
forall (m :: * -> *) a. Monad m => a -> m a
return (Async (([FileDiagnostic], Maybe HscEnvEq), [String])
asyncRes, forall a. Async a -> IO a
wait Async (([FileDiagnostic], Maybe HscEnvEq), [String])
asyncRes)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (([FileDiagnostic], Maybe HscEnvEq), [String])
opts
cradleToOptsAndLibDir :: Recorder (WithPriority Log) -> Cradle Void -> FilePath
-> IO (Either [CradleError] (ComponentOptions, FilePath))
cradleToOptsAndLibDir :: Recorder (WithPriority Log)
-> Cradle Void
-> String
-> IO (Either [CradleError] (ComponentOptions, String))
cradleToOptsAndLibDir Recorder (WithPriority Log)
recorder Cradle Void
cradle String
file = do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug forall a b. (a -> b) -> a -> b
$ Cradle Void -> Log
LogCradle Cradle Void
cradle
let logger :: LogAction IO (WithSeverity Log)
logger = forall (m :: * -> *) msg.
(MonadIO m, HasCallStack) =>
Recorder (WithPriority msg) -> LogAction m (WithSeverity msg)
toCologActionWithPrio forall a b. (a -> b) -> a -> b
$ forall a b.
(a -> b) -> Recorder (WithPriority b) -> Recorder (WithPriority a)
cmapWithPrio Log -> Log
LogHieBios Recorder (WithPriority Log)
recorder
CradleLoadResult ComponentOptions
cradleRes <- forall a.
LogAction IO (WithSeverity Log)
-> String -> Cradle a -> IO (CradleLoadResult ComponentOptions)
HieBios.getCompilerOptions LogAction IO (WithSeverity Log)
logger String
file Cradle Void
cradle
case CradleLoadResult ComponentOptions
cradleRes of
CradleSuccess ComponentOptions
r -> do
CradleLoadResult String
libDirRes <- forall a.
LogAction IO (WithSeverity Log)
-> Cradle a -> IO (CradleLoadResult String)
getRuntimeGhcLibDir LogAction IO (WithSeverity Log)
logger Cradle Void
cradle
case CradleLoadResult String
libDirRes of
CradleSuccess String
libDir -> forall (f :: * -> *) a. Applicative f => a -> f a
pure (forall a b. b -> Either a b
Right (ComponentOptions
r, String
libDir))
CradleFail CradleError
err -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left [CradleError
err])
CradleLoadResult String
CradleNone -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info forall a b. (a -> b) -> a -> b
$ String -> Log
LogNoneCradleFound String
file
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left [])
CradleFail CradleError
err -> forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left [CradleError
err])
CradleLoadResult ComponentOptions
CradleNone -> do
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info forall a b. (a -> b) -> a -> b
$ String -> Log
LogNoneCradleFound String
file
forall (m :: * -> *) a. Monad m => a -> m a
return (forall a b. a -> Either a b
Left [])
#if MIN_VERSION_ghc(9,3,0)
emptyHscEnv :: NameCache -> FilePath -> IO HscEnv
#else
emptyHscEnv :: IORef NameCache -> FilePath -> IO HscEnv
#endif
emptyHscEnv :: IORef NameCache -> String -> IO HscEnv
emptyHscEnv IORef NameCache
nc String
libDir = do
HscEnv
env <- forall a. Maybe String -> Ghc a -> IO a
runGhc (forall a. a -> Maybe a
Just String
libDir) forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ IORef NameCache -> HscEnv -> HscEnv
setNameCache IORef NameCache
nc (DynFlags -> HscEnv -> HscEnv
hscSetFlags ((HscEnv -> DynFlags
hsc_dflags HscEnv
env){useUnicode :: Bool
useUnicode = Bool
True }) HscEnv
env)
data TargetDetails = TargetDetails
{
TargetDetails -> Target
targetTarget :: !Target,
TargetDetails -> ([FileDiagnostic], Maybe HscEnvEq)
targetEnv :: !(IdeResult HscEnvEq),
TargetDetails -> DependencyInfo
targetDepends :: !DependencyInfo,
TargetDetails -> [NormalizedFilePath]
targetLocations :: ![NormalizedFilePath]
}
fromTargetId :: [FilePath]
-> [String]
-> TargetId
-> IdeResult HscEnvEq
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId :: [String]
-> [String]
-> TargetId
-> ([FileDiagnostic], Maybe HscEnvEq)
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId [String]
is [String]
exts (GHC.TargetModule ModuleName
modName) ([FileDiagnostic], Maybe HscEnvEq)
env DependencyInfo
dep = do
let fps :: [String]
fps = [String
i String -> ShowS
</> ModuleName -> String
moduleNameSlashes ModuleName
modName String -> ShowS
-<.> String
ext forall a. Semigroup a => a -> a -> a
<> String
boot
| String
ext <- [String]
exts
, String
i <- [String]
is
, String
boot <- [String
"", String
"-boot"]
]
[NormalizedFilePath]
locs <- forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap String -> NormalizedFilePath
toNormalizedFilePath' forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> IO String
makeAbsolute) [String]
fps
forall (m :: * -> *) a. Monad m => a -> m a
return [Target
-> ([FileDiagnostic], Maybe HscEnvEq)
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (ModuleName -> Target
TargetModule ModuleName
modName) ([FileDiagnostic], Maybe HscEnvEq)
env DependencyInfo
dep [NormalizedFilePath]
locs]
fromTargetId [String]
_ [String]
_ (GHC.TargetFile String
f Maybe Phase
_) ([FileDiagnostic], Maybe HscEnvEq)
env DependencyInfo
deps = do
NormalizedFilePath
nf <- String -> NormalizedFilePath
toNormalizedFilePath' forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String -> IO String
makeAbsolute String
f
forall (m :: * -> *) a. Monad m => a -> m a
return [Target
-> ([FileDiagnostic], Maybe HscEnvEq)
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (NormalizedFilePath -> Target
TargetFile NormalizedFilePath
nf) ([FileDiagnostic], Maybe HscEnvEq)
env DependencyInfo
deps [NormalizedFilePath
nf]]
toFlagsMap :: TargetDetails -> [(NormalizedFilePath, (IdeResult HscEnvEq, DependencyInfo))]
toFlagsMap :: TargetDetails
-> [(NormalizedFilePath,
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))]
toFlagsMap TargetDetails{[NormalizedFilePath]
([FileDiagnostic], Maybe HscEnvEq)
DependencyInfo
Target
targetLocations :: [NormalizedFilePath]
targetDepends :: DependencyInfo
targetEnv :: ([FileDiagnostic], Maybe HscEnvEq)
targetTarget :: Target
targetLocations :: TargetDetails -> [NormalizedFilePath]
targetDepends :: TargetDetails -> DependencyInfo
targetEnv :: TargetDetails -> ([FileDiagnostic], Maybe HscEnvEq)
targetTarget :: TargetDetails -> Target
..} =
[ (NormalizedFilePath
l, (([FileDiagnostic], Maybe HscEnvEq)
targetEnv, DependencyInfo
targetDepends)) | NormalizedFilePath
l <- [NormalizedFilePath]
targetLocations]
#if MIN_VERSION_ghc(9,3,0)
setNameCache :: NameCache -> HscEnv -> HscEnv
#else
setNameCache :: IORef NameCache -> HscEnv -> HscEnv
#endif
setNameCache :: IORef NameCache -> HscEnv -> HscEnv
setNameCache IORef NameCache
nc HscEnv
hsc = HscEnv
hsc { hsc_NC :: IORef NameCache
hsc_NC = IORef NameCache
nc }
newComponentCache
:: Recorder (WithPriority Log)
-> [String]
-> Maybe FilePath
-> NormalizedFilePath
-> HscEnv
-> [(UnitId, DynFlags)]
-> ComponentInfo
-> IO ( [TargetDetails], (IdeResult HscEnvEq, DependencyInfo))
newComponentCache :: Recorder (WithPriority Log)
-> [String]
-> Maybe String
-> NormalizedFilePath
-> HscEnv
-> [(UnitId, DynFlags)]
-> ComponentInfo
-> IO
([TargetDetails],
(([FileDiagnostic], Maybe HscEnvEq), DependencyInfo))
newComponentCache Recorder (WithPriority Log)
recorder [String]
exts Maybe String
cradlePath NormalizedFilePath
cfp HscEnv
hsc_env [(UnitId, DynFlags)]
uids ComponentInfo
ci = do
let df :: DynFlags
df = ComponentInfo -> DynFlags
componentDynFlags ComponentInfo
ci
HscEnv
hscEnv' <-
#if MIN_VERSION_ghc(9,3,0)
Compat.initUnits (map snd uids) (hscSetFlags df hsc_env)
#else
forall b. HscEnv -> Ghc b -> IO b
evalGhcEnv HscEnv
hsc_env forall a b. (a -> b) -> a -> b
$ do
()
_ <- forall (m :: * -> *). GhcMonad m => DynFlags -> m ()
setSessionDynFlags forall a b. (a -> b) -> a -> b
$ DynFlags
df
forall (m :: * -> *). GhcMonad m => m HscEnv
getSession
#endif
let newFunc :: HscEnv -> [(UnitId, DynFlags)] -> IO HscEnvEq
newFunc = forall b a. b -> (a -> b) -> Maybe a -> b
maybe HscEnv -> [(UnitId, DynFlags)] -> IO HscEnvEq
newHscEnvEqPreserveImportPaths String -> HscEnv -> [(UnitId, DynFlags)] -> IO HscEnvEq
newHscEnvEq Maybe String
cradlePath
HscEnvEq
henv <- HscEnv -> [(UnitId, DynFlags)] -> IO HscEnvEq
newFunc HscEnv
hscEnv' [(UnitId, DynFlags)]
uids
let targetEnv :: ([FileDiagnostic], Maybe HscEnvEq)
targetEnv = ([], forall a. a -> Maybe a
Just HscEnvEq
henv)
targetDepends :: DependencyInfo
targetDepends = ComponentInfo -> DependencyInfo
componentDependencyInfo ComponentInfo
ci
res :: (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
res = (([FileDiagnostic], Maybe HscEnvEq)
targetEnv, DependencyInfo
targetDepends)
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Debug forall a b. (a -> b) -> a -> b
$ (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo) -> Log
LogNewComponentCache (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
res
forall a. a -> IO a
evaluate forall a b. (a -> b) -> a -> b
$ forall (f :: * -> *) a. NFData1 f => (a -> ()) -> f a -> ()
liftRnf forall a. a -> ()
rwhnf forall a b. (a -> b) -> a -> b
$ ComponentInfo -> [Target]
componentTargets ComponentInfo
ci
let mk :: Target -> IO [TargetDetails]
mk Target
t = [String]
-> [String]
-> TargetId
-> ([FileDiagnostic], Maybe HscEnvEq)
-> DependencyInfo
-> IO [TargetDetails]
fromTargetId (DynFlags -> [String]
importPaths DynFlags
df) [String]
exts (Target -> TargetId
targetId Target
t) ([FileDiagnostic], Maybe HscEnvEq)
targetEnv DependencyInfo
targetDepends
[TargetDetails]
ctargets <- forall (m :: * -> *) a b. Monad m => (a -> m [b]) -> [a] -> m [b]
concatMapM Target -> IO [TargetDetails]
mk (ComponentInfo -> [Target]
componentTargets ComponentInfo
ci)
let special_target :: TargetDetails
special_target = Target
-> ([FileDiagnostic], Maybe HscEnvEq)
-> DependencyInfo
-> [NormalizedFilePath]
-> TargetDetails
TargetDetails (NormalizedFilePath -> Target
TargetFile NormalizedFilePath
cfp) ([FileDiagnostic], Maybe HscEnvEq)
targetEnv DependencyInfo
targetDepends [ComponentInfo -> NormalizedFilePath
componentFP ComponentInfo
ci]
forall (m :: * -> *) a. Monad m => a -> m a
return (TargetDetails
special_targetforall a. a -> [a] -> [a]
:[TargetDetails]
ctargets, (([FileDiagnostic], Maybe HscEnvEq), DependencyInfo)
res)
setCacheDirs :: MonadUnliftIO m => Recorder (WithPriority Log) -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs :: forall (m :: * -> *).
MonadUnliftIO m =>
Recorder (WithPriority Log) -> CacheDirs -> DynFlags -> m DynFlags
setCacheDirs Recorder (WithPriority Log)
recorder 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
forall (m :: * -> *) msg.
(HasCallStack, MonadIO m) =>
Recorder (WithPriority msg) -> Priority -> msg -> m ()
logWith Recorder (WithPriority Log)
recorder Priority
Info forall a b. (a -> b) -> a -> b
$ String -> Log
LogInterfaceFilesCacheDir (forall a. a -> Maybe a -> a
fromMaybe String
cacheDir Maybe String
hiCacheDir)
forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ DynFlags
dflags
forall a b. a -> (a -> b) -> b
& forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id String -> DynFlags -> DynFlags
setHiDir Maybe String
hiCacheDir
forall a b. a -> (a -> b) -> b
& forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id String -> DynFlags -> DynFlags
setHieDir Maybe String
hieCacheDir
forall a b. a -> (a -> b) -> b
& forall b a. b -> (a -> b) -> Maybe a -> b
maybe forall a. a -> a
id String -> DynFlags -> DynFlags
setODir Maybe String
oCacheDir
type DependencyInfo = Map.Map FilePath (Maybe UTCTime)
type HieMap = Map.Map (Maybe FilePath) (HscEnv, [RawComponentInfo])
type FlagsMap = Map.Map (Maybe FilePath) (HM.HashMap NormalizedFilePath (IdeResult HscEnvEq, DependencyInfo))
type FilesMap = HM.HashMap NormalizedFilePath (Maybe FilePath)
data RawComponentInfo = RawComponentInfo
{ RawComponentInfo -> UnitId
rawComponentUnitId :: UnitId
, RawComponentInfo -> DynFlags
rawComponentDynFlags :: DynFlags
, RawComponentInfo -> [Target]
rawComponentTargets :: [GHC.Target]
, RawComponentInfo -> NormalizedFilePath
rawComponentFP :: NormalizedFilePath
, RawComponentInfo -> ComponentOptions
rawComponentCOptions :: ComponentOptions
, RawComponentInfo -> DependencyInfo
rawComponentDependencyInfo :: DependencyInfo
}
data ComponentInfo = ComponentInfo
{ ComponentInfo -> UnitId
componentUnitId :: UnitId
, ComponentInfo -> DynFlags
componentDynFlags :: DynFlags
, ComponentInfo -> [UnitId]
_componentInternalUnits :: [UnitId]
, ComponentInfo -> [Target]
componentTargets :: [GHC.Target]
, ComponentInfo -> NormalizedFilePath
componentFP :: NormalizedFilePath
, ComponentInfo -> ComponentOptions
_componentCOptions :: ComponentOptions
, ComponentInfo -> DependencyInfo
componentDependencyInfo :: DependencyInfo
}
checkDependencyInfo :: DependencyInfo -> IO Bool
checkDependencyInfo :: DependencyInfo -> IO Bool
checkDependencyInfo DependencyInfo
old_di = do
DependencyInfo
di <- [String] -> IO DependencyInfo
getDependencyInfo (forall k a. Map k a -> [k]
Map.keys DependencyInfo
old_di)
forall (m :: * -> *) a. Monad m => a -> m a
return (DependencyInfo
di forall a. Eq a => a -> a -> Bool
== DependencyInfo
old_di)
getDependencyInfo :: [FilePath] -> IO DependencyInfo
getDependencyInfo :: [String] -> IO DependencyInfo
getDependencyInfo [String]
fs = forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> 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
safeTryIO :: IO a -> IO (Either IOException a)
safeTryIO :: forall a. IO a -> IO (Either IOException a)
safeTryIO = forall (m :: * -> *) e a.
(MonadCatch m, Exception e) =>
m a -> m (Either e a)
Safe.try
do_one :: FilePath -> IO (FilePath, Maybe UTCTime)
do_one :: String -> IO (String, Maybe UTCTime)
do_one String
fp = (String
fp,) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. Either a b -> Maybe b
eitherToMaybe forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. IO a -> IO (Either IOException a)
safeTryIO (String -> IO UTCTime
getModificationTime String
fp)
_removeInplacePackages
:: UnitId
-> [UnitId]
-> DynFlags
-> (DynFlags, [UnitId])
_removeInplacePackages :: UnitId -> [UnitId] -> DynFlags -> (DynFlags, [UnitId])
_removeInplacePackages UnitId
fake_uid [UnitId]
us DynFlags
df = (UnitId -> DynFlags -> DynFlags
setHomeUnitId_ UnitId
fake_uid forall a b. (a -> b) -> a -> b
$
DynFlags
df { packageFlags :: [PackageFlag]
packageFlags = [PackageFlag]
ps }, [UnitId]
uids)
where
([UnitId]
uids, [PackageFlag]
ps) = [UnitId] -> [PackageFlag] -> ([UnitId], [PackageFlag])
Compat.filterInplaceUnits [UnitId]
us (DynFlags -> [PackageFlag]
packageFlags DynFlags
df)
memoIO :: Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO :: forall a b. Ord a => (a -> IO b) -> IO (a -> IO b)
memoIO a -> IO b
op = do
Var (Map a (IO b))
ref <- forall a. a -> IO (Var a)
newVar forall k a. Map k a
Map.empty
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ \a
k -> forall (m :: * -> *) a. Monad m => m (m a) -> m a
join forall a b. (a -> b) -> a -> b
$ forall (m :: * -> *) a. MonadMask m => m a -> m a
mask_ forall a b. (a -> b) -> a -> b
$ forall a b. Var a -> (a -> IO (a, b)) -> IO b
modifyVar Var (Map a (IO b))
ref forall a b. (a -> b) -> a -> b
$ \Map a (IO b)
mp ->
case 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 <- forall a. IO a -> IO (IO a)
onceFork forall a b. (a -> b) -> a -> b
$ a -> IO b
op a
k
forall (m :: * -> *) a. Monad m => a -> m a
return (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 -> forall (m :: * -> *) a. Monad m => a -> m a
return (Map a (IO b)
mp, IO b
res)
setOptions :: GhcMonad m => ComponentOptions -> DynFlags -> m (DynFlags, [GHC.Target])
setOptions :: forall (m :: * -> *).
GhcMonad m =>
ComponentOptions -> DynFlags -> m (DynFlags, [Target])
setOptions (ComponentOptions [String]
theOpts String
compRoot [String]
_) DynFlags
dflags = do
(DynFlags
dflags', [Target]
targets') <- 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 forall a b. (a -> b) -> a -> b
$
forall a b c. (a -> b -> c) -> b -> a -> c
flip DynFlags -> GeneralFlag -> DynFlags
gopt_unset GeneralFlag
Opt_WriteInterface forall a b. (a -> b) -> a -> b
$
DynFlags -> DynFlags
dontWriteHieFiles forall a b. (a -> b) -> a -> b
$
DynFlags -> DynFlags
setIgnoreInterfacePragmas forall a b. (a -> b) -> a -> b
$
DynFlags -> DynFlags
setBytecodeLinkerOptions forall a b. (a -> b) -> a -> b
$
DynFlags -> DynFlags
disableOptimisation forall a b. (a -> b) -> a -> b
$
DynFlags -> DynFlags
Compat.setUpTypedHoles forall a b. (a -> b) -> a -> b
$
String -> DynFlags -> DynFlags
makeDynFlagsAbsolute String
compRoot DynFlags
dflags'
DynFlags
final_flags <- forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO forall a b. (a -> b) -> a -> b
$ forall a. IO a -> IO a
wrapPackageSetupException forall a b. (a -> b) -> a -> b
$ DynFlags -> IO DynFlags
Compat.oldInitUnits DynFlags
dflags''
forall (m :: * -> *) a. Monad m => a -> m a
return (DynFlags
final_flags, [Target]
targets)
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 =
DynFlags
d { hiDir :: Maybe String
hiDir = forall a. a -> Maybe a
Just String
f}
setODir :: FilePath -> DynFlags -> DynFlags
setODir :: String -> DynFlags -> DynFlags
setODir String
f DynFlags
d =
DynFlags
d { objectDir :: Maybe String
objectDir = 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 <- forall a. a -> Maybe a
Just forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> XdgDirectory -> String -> IO String
getXdgDirectory XdgDirectory
XdgCache (String
cacheDir String -> ShowS
</> String
prefix forall a. [a] -> [a] -> [a]
++ String
"-" forall a. [a] -> [a] -> [a]
++ String
opts_hash)
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Maybe String -> Maybe String -> Maybe String -> CacheDirs
CacheDirs Maybe String
dir Maybe String
dir Maybe String
dir
where
opts_hash :: String
opts_hash = ByteString -> String
B.unpack forall a b. (a -> b) -> a -> b
$ ByteString -> ByteString
B16.encode forall a b. (a -> b) -> a -> b
$ Ctx -> ByteString
H.finalize forall a b. (a -> b) -> a -> b
$ Ctx -> [ByteString] -> Ctx
H.updates Ctx
H.init (forall a b. (a -> b) -> [a] -> [b]
map String -> ByteString
B.pack [String]
opts)
cacheDir :: String
cacheDir :: String
cacheDir = String
"ghcide"
data PackageSetupException
= PackageSetupException
{ PackageSetupException -> String
message :: !String
}
| GhcVersionMismatch
{ PackageSetupException -> Version
compileTime :: !Version
, PackageSetupException -> Version
runTime :: !Version
}
| PackageCheckFailed !NotCompatibleReason
deriving (PackageSetupException -> PackageSetupException -> Bool
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 -> ShowS
[PackageSetupException] -> ShowS
PackageSetupException -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [PackageSetupException] -> ShowS
$cshowList :: [PackageSetupException] -> ShowS
show :: PackageSetupException -> String
$cshow :: PackageSetupException -> String
showsPrec :: Int -> PackageSetupException -> ShowS
$cshowsPrec :: Int -> PackageSetupException -> ShowS
Show, Typeable)
instance Exception PackageSetupException
wrapPackageSetupException :: IO a -> IO a
wrapPackageSetupException :: forall a. IO a -> IO a
wrapPackageSetupException = forall (m :: * -> *) a.
MonadCatch m =>
(SomeException -> m a) -> m a -> m a
handleAny forall a b. (a -> b) -> a -> b
$ \case
SomeException
e | Just (PackageSetupException
pkgE :: PackageSetupException) <- forall e. Exception e => SomeException -> Maybe e
fromException SomeException
e -> forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO PackageSetupException
pkgE
SomeException
e -> (forall (m :: * -> *) e a. (MonadThrow m, Exception e) => e -> m a
throwIO forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> PackageSetupException
PackageSetupException forall b c a. (b -> c) -> (a -> b) -> a -> c
. 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 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 forall a. Semigroup a => a -> a -> a
<> String
"-" forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime
,String
"but project uses package"
, String
packageName forall a. Semigroup a => a -> a -> a
<> 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-" forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime forall a. Semigroup a => a -> a -> a
<> String
"-" forall a. Semigroup a => a -> a -> a
<> String
compileTimeAbi
,String
"but project uses base-" forall a. Semigroup a => a -> a -> a
<> Version -> String
showVersion Version
compileTime forall a. Semigroup a => a -> a -> a
<> 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 -> FileDiagnostic
renderPackageSetupException String
fp PackageSetupException
e =
forall a.
Maybe Text
-> Maybe DiagnosticSeverity
-> a
-> Text
-> (a, ShowDiagnostic, Diagnostic)
ideErrorWithSource (forall a. a -> Maybe a
Just Text
"cradle") (forall a. a -> Maybe a
Just DiagnosticSeverity
DiagnosticSeverity_Error) (String -> NormalizedFilePath
toNormalizedFilePath' String
fp) (String -> Text
T.pack forall a b. (a -> b) -> a -> b
$ PackageSetupException -> String
showPackageSetupException PackageSetupException
e)