@@ -15,11 +15,11 @@ import Control.Concurrent.Extra
15
15
import Control.Exception
16
16
import Control.Monad.Extra
17
17
import Control.Monad.IO.Class
18
- import qualified Crypto.Hash.SHA1 as H
19
- import Data.ByteString.Base16
20
- import qualified Data.ByteString.Char8 as B
18
+ -- import qualified Crypto.Hash.SHA1 as H
19
+ -- import Data.ByteString.Base16
20
+ -- import qualified Data.ByteString.Char8 as B
21
21
import Data.Default
22
- import Data.Functor ((<&>) )
22
+ -- import Data.Functor ((<&>))
23
23
import qualified Data.HashSet as HashSet
24
24
import Data.List.Extra
25
25
import qualified Data.Map.Strict as Map
@@ -43,24 +43,26 @@ import Development.IDE.Types.Diagnostics
43
43
import Development.IDE.Types.Location
44
44
import Development.IDE.Types.Logger
45
45
import Development.IDE.Types.Options
46
- import Development.Shake (Action , Rules , action , doesFileExist , doesDirectoryExist , need )
47
- import DynFlags
48
- import GHC hiding (def )
46
+ import Development.Shake (Action , Rules , action )
47
+ -- import DynFlags
48
+ -- import GHC hiding (def)
49
49
-- import qualified GHC.Paths
50
50
import HIE.Bios
51
- import HIE.Bios.Cradle
52
- import HIE.Bios.Environment
53
- import HIE.Bios.Types
51
+ import qualified Language.Haskell.LSP.Core as LSP
52
+ -- import HIE.Bios.Cradle
53
+ -- import HIE.Bios.Environment
54
+ -- import HIE.Bios.Types
54
55
import Ide.Plugin
55
56
-- import Ide.PluginDescriptors
56
57
import Ide.Plugin.Config
57
58
-- import Ide.Plugin.Formatter
58
59
import Language.Haskell.LSP.Messages
59
60
import Language.Haskell.LSP.Types (LspId (IdInt ))
60
- import qualified Language.Haskell.LSP.Core as LSP
61
- import Linker
61
+ -- import qualified Language.Haskell.LSP.Core as LSP
62
+ -- import Linker
62
63
-- import Paths_haskell_language_server
63
64
import RuleTypes
65
+ import Rules
64
66
import qualified System.Directory.Extra as IO
65
67
-- import System.Environment
66
68
import System.Exit
@@ -139,6 +141,7 @@ idePlugins includeExamples
139
141
140
142
-- ---------------------------------------------------------------------
141
143
-- Prefix for the cache path
144
+ {-
142
145
cacheDir :: String
143
146
cacheDir = "ghcide"
144
147
@@ -148,7 +151,7 @@ getCacheDir opts = IO.getXdgDirectory IO.XdgCache (cacheDir </> opts_hash)
148
151
-- Create a unique folder per set of different GHC options, assuming that each different set of
149
152
-- GHC options will create incompatible interface files.
150
153
opts_hash = B.unpack $ encode $ H.finalize $ H.updates H.init (map B.pack opts)
151
-
154
+ -}
152
155
153
156
main :: IO ()
154
157
main = do
@@ -184,6 +187,7 @@ main = do
184
187
let options = (defaultIdeOptions $ loadSession dir)
185
188
{ optReportProgress = clientSupportsProgress caps
186
189
, optShakeProfiling = argsShakeProfiling
190
+ , optTesting = IdeTesting argsTesting
187
191
}
188
192
debouncer <- newAsyncDebouncer
189
193
initialise caps (cradleRules >> mainRule >> pluginRules plugins >> action kick)
@@ -239,7 +243,7 @@ main = do
239
243
240
244
cradleRules :: Rules ()
241
245
cradleRules = do
242
- loadGhcSessionIO
246
+ loadGhcSession
243
247
cradleToSession
244
248
245
249
expandFiles :: [FilePath ] -> IO [FilePath ]
@@ -267,95 +271,6 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath -> file) diags) =
267
271
withLock lock $ T. putStrLn $ showDiagnosticsColored $ map (file,ShowDiag ,) diags
268
272
showEvent lock e = withLock lock $ print e
269
273
270
-
271
- loadGhcSessionIO :: Rules ()
272
- loadGhcSessionIO =
273
- -- This rule is for caching the GHC session. E.g., even when the cabal file
274
- -- changed, if the resulting flags did not change, we would continue to use
275
- -- the existing session.
276
- defineNoFile $ \ (GetHscEnv opts deps) ->
277
- liftIO $ createSession $ ComponentOptions opts deps
278
-
279
-
280
- getComponentOptions :: Cradle a -> IO ComponentOptions
281
- getComponentOptions cradle = do
282
- let showLine s = putStrLn (" > " ++ s)
283
- -- WARNING 'runCradle is very expensive and must be called as few times as possible
284
- cradleRes <- runCradle (cradleOptsProg cradle) showLine " "
285
- case cradleRes of
286
- CradleSuccess r -> pure r
287
- CradleFail err -> throwIO err
288
- -- TODO Rather than failing here, we should ignore any files that use this cradle.
289
- -- That will require some more changes.
290
- CradleNone -> fail " 'none' cradle is not yet supported"
291
-
292
-
293
- createSession :: ComponentOptions -> IO HscEnvEq
294
- createSession (ComponentOptions theOpts _) = do
295
- libdir <- getLibdir
296
-
297
- cacheDir <- Main. getCacheDir theOpts
298
-
299
- env <- runGhc (Just libdir) $ do
300
- dflags <- getSessionDynFlags
301
- (dflags', _targets) <- addCmdOpts theOpts dflags
302
- _ <- setSessionDynFlags $
303
- -- disabled, generated directly by ghcide instead
304
- flip gopt_unset Opt_WriteInterface $
305
- -- disabled, generated directly by ghcide instead
306
- -- also, it can confuse the interface stale check
307
- dontWriteHieFiles $
308
- setHiDir cacheDir $
309
- setDefaultHieDir cacheDir $
310
- setIgnoreInterfacePragmas $
311
- setLinkerOptions $
312
- disableOptimisation dflags'
313
- getSession
314
- initDynLinker env
315
- newHscEnvEq env
316
-
317
- -- we don't want to generate object code so we compile to bytecode
318
- -- (HscInterpreted) which implies LinkInMemory
319
- -- HscInterpreted
320
- setLinkerOptions :: DynFlags -> DynFlags
321
- setLinkerOptions df = df {
322
- ghcLink = LinkInMemory
323
- , hscTarget = HscNothing
324
- , ghcMode = CompManager
325
- }
326
-
327
- setIgnoreInterfacePragmas :: DynFlags -> DynFlags
328
- setIgnoreInterfacePragmas df =
329
- gopt_set (gopt_set df Opt_IgnoreInterfacePragmas ) Opt_IgnoreOptimChanges
330
-
331
- disableOptimisation :: DynFlags -> DynFlags
332
- disableOptimisation df = updOptLevel 0 df
333
-
334
- setHiDir :: FilePath -> DynFlags -> DynFlags
335
- setHiDir f d =
336
- -- override user settings to avoid conflicts leading to recompilation
337
- d { hiDir = Just f}
338
-
339
- cradleToSession :: Rules ()
340
- cradleToSession = define $ \ LoadCradle nfp -> do
341
- let f = fromNormalizedFilePath nfp
342
-
343
- -- If the path points to a directory, load the implicit cradle
344
- mbYaml <- doesDirectoryExist f <&> \ isDir -> if isDir then Nothing else Just f
345
- cradle <- liftIO $ maybe (loadImplicitCradle $ addTrailingPathSeparator f) loadCradle mbYaml
346
-
347
- cmpOpts <- liftIO $ getComponentOptions cradle
348
- let opts = componentOptions cmpOpts
349
- deps = componentDependencies cmpOpts
350
- deps' = case mbYaml of
351
- -- For direct cradles, the hie.yaml file itself must be watched.
352
- Just yaml | isDirectCradle cradle -> yaml : deps
353
- _ -> deps
354
- existingDeps <- filterM doesFileExist deps'
355
- need existingDeps
356
- ([] ,) . pure <$> useNoFile_ (GetHscEnv opts deps)
357
-
358
-
359
274
loadSession :: FilePath -> Action (FilePath -> Action HscEnvEq )
360
275
loadSession dir = liftIO $ do
361
276
cradleLoc <- memoIO $ \ v -> do
0 commit comments