3
3
{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
4
4
{-# LANGUAGE CPP #-} -- To get precise GHC version
5
5
{-# LANGUAGE TemplateHaskell #-}
6
+ {-# LANGUAGE TypeFamilies #-}
6
7
7
8
module Main (main ) where
8
9
9
10
import Arguments
11
+ import Data.Binary (Binary )
12
+ import Data.Dynamic (Typeable )
13
+ import Data.Hashable (Hashable )
10
14
import Data.Maybe
11
15
import Data.List.Extra
12
16
import System.FilePath
13
17
import Control.Concurrent.Extra
18
+ import Control.DeepSeq (NFData )
14
19
import Control.Exception
15
20
import Control.Monad.Extra
16
21
import Control.Monad.IO.Class
@@ -39,20 +44,22 @@ import Language.Haskell.LSP.Types (LspId(IdInt))
39
44
import Linker
40
45
import Data.Version
41
46
import Development.IDE.LSP.LanguageServer
42
- import System.Directory.Extra as IO
47
+ import qualified System.Directory.Extra as IO
43
48
import System.Environment
44
49
import System.IO
45
50
import System.Exit
46
51
import Paths_ghcide
47
52
import Development.GitRev
48
- import Development.Shake (Action , action )
53
+ import Development.Shake (Action , RuleResult , Rules , action , doesFileExist , need )
49
54
import qualified Data.HashSet as HashSet
50
55
import qualified Data.Map.Strict as Map
51
56
52
57
import GHC hiding (def )
58
+ import GHC.Generics (Generic )
53
59
import qualified GHC.Paths
54
60
55
61
import HIE.Bios
62
+ import HIE.Bios.Cradle
56
63
import HIE.Bios.Types
57
64
58
65
-- Set the GHC libdir to the nix libdir if it's present.
@@ -84,9 +91,9 @@ main = do
84
91
let logger p = Logger $ \ pri msg -> when (pri >= p) $ withLock lock $
85
92
T. putStrLn $ T. pack (" [" ++ upper (show pri) ++ " ] " ) <> msg
86
93
87
- whenJust argsCwd setCurrentDirectory
94
+ whenJust argsCwd IO. setCurrentDirectory
88
95
89
- dir <- getCurrentDirectory
96
+ dir <- IO. getCurrentDirectory
90
97
91
98
let plugins = Completions. plugin <> CodeAction. plugin
92
99
onInitialConfiguration = const $ Right ()
@@ -99,22 +106,21 @@ main = do
99
106
runLanguageServer def (pluginHandler plugins) onInitialConfiguration onConfigurationChange $ \ getLspId event vfs caps -> do
100
107
t <- t
101
108
hPutStrLn stderr $ " Started LSP server in " ++ showDuration t
102
- -- very important we only call loadSession once, and it's fast, so just do it before starting
103
- session <- loadSession dir
104
- let options = (defaultIdeOptions $ return session)
109
+ let options = (defaultIdeOptions $ loadSession dir)
105
110
{ optReportProgress = clientSupportsProgress caps
106
111
, optShakeProfiling = argsShakeProfiling
107
112
}
108
113
debouncer <- newAsyncDebouncer
109
- initialise caps (mainRule >> pluginRules plugins >> action kick) getLspId event (logger minBound ) debouncer options vfs
114
+ initialise caps (loadGhcSessionIO >> mainRule >> pluginRules plugins >> action kick)
115
+ getLspId event (logger minBound ) debouncer options vfs
110
116
else do
111
117
putStrLn $ " Ghcide setup tester in " ++ dir ++ " ."
112
118
putStrLn " Report bugs at https://github.com/digital-asset/ghcide/issues"
113
119
114
120
putStrLn $ " \n Step 1/6: Finding files to test in " ++ dir
115
121
files <- expandFiles (argFiles ++ [" ." | null argFiles])
116
122
-- LSP works with absolute file paths, so try and behave similarly
117
- files <- nubOrd <$> mapM canonicalizePath files
123
+ files <- nubOrd <$> mapM IO. canonicalizePath files
118
124
putStrLn $ " Found " ++ show (length files) ++ " files"
119
125
120
126
putStrLn " \n Step 2/6: Looking for hie.yaml files that control setup"
@@ -128,7 +134,8 @@ main = do
128
134
cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle x
129
135
when (isNothing x) $ print cradle
130
136
putStrLn $ " \n Step 4/6, Cradle " ++ show i ++ " /" ++ show n ++ " : Loading GHC Session"
131
- cradleToSession cradle
137
+ opts <- getComponentOptions cradle
138
+ createSession opts
132
139
133
140
putStrLn " \n Step 5/6: Initializing the IDE"
134
141
vfs <- makeVFSHandle
@@ -141,7 +148,7 @@ main = do
141
148
let options =
142
149
(defaultIdeOptions $ return $ return . grab)
143
150
{ optShakeProfiling = argsShakeProfiling }
144
- ide <- initialise def mainRule (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
151
+ ide <- initialise def (loadGhcSessionIO >> mainRule) (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
145
152
146
153
putStrLn " \n Step 6/6: Type checking the files"
147
154
setFilesOfInterest ide $ HashSet. fromList $ map toNormalizedFilePath files
@@ -163,7 +170,7 @@ expandFiles = concatMapM $ \x -> do
163
170
let recurse " ." = True
164
171
recurse x | " ." `isPrefixOf` takeFileName x = False -- skip .git etc
165
172
recurse x = takeFileName x `notElem` [" dist" ," dist-newstyle" ] -- cabal directories
166
- files <- filter (\ x -> takeExtension x `elem` [" .hs" ," .lhs" ]) <$> listFilesInside (return . recurse) x
173
+ files <- filter (\ x -> takeExtension x `elem` [" .hs" ," .lhs" ]) <$> IO. listFilesInside (return . recurse) x
167
174
when (null files) $
168
175
fail $ " Couldn't find any .hs/.lhs files inside directory: " ++ x
169
176
return files
@@ -182,16 +189,42 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath -> file) diags) =
182
189
showEvent lock e = withLock lock $ print e
183
190
184
191
185
- cradleToSession :: Cradle a -> IO HscEnvEq
186
- cradleToSession cradle = do
192
+ -- Rule type for caching GHC sessions.
193
+ type instance RuleResult GetHscEnv = HscEnvEq
194
+
195
+ data GetHscEnv = GetHscEnv
196
+ { hscenvOptions :: [String ] -- componentOptions from hie-bios
197
+ , hscenvDependencies :: [FilePath ] -- componentDependencies from hie-bios
198
+ }
199
+ deriving (Eq , Show , Typeable , Generic )
200
+ instance Hashable GetHscEnv
201
+ instance NFData GetHscEnv
202
+ instance Binary GetHscEnv
203
+
204
+
205
+ loadGhcSessionIO :: Rules ()
206
+ loadGhcSessionIO =
207
+ -- This rule is for caching the GHC session. E.g., even when the cabal file
208
+ -- changed, if the resulting flags did not change, we would continue to use
209
+ -- the existing session.
210
+ defineNoFile $ \ (GetHscEnv opts deps) ->
211
+ liftIO $ createSession $ ComponentOptions opts deps
212
+
213
+
214
+ getComponentOptions :: Cradle a -> IO ComponentOptions
215
+ getComponentOptions cradle = do
187
216
let showLine s = putStrLn (" > " ++ s)
188
217
cradleRes <- runCradle (cradleOptsProg cradle) showLine " "
189
- opts <- case cradleRes of
218
+ case cradleRes of
190
219
CradleSuccess r -> pure r
191
220
CradleFail err -> throwIO err
192
221
-- TODO Rather than failing here, we should ignore any files that use this cradle.
193
222
-- That will require some more changes.
194
223
CradleNone -> fail " 'none' cradle is not yet supported"
224
+
225
+
226
+ createSession :: ComponentOptions -> IO HscEnvEq
227
+ createSession opts = do
195
228
libdir <- getLibdir
196
229
env <- runGhc (Just libdir) $ do
197
230
_targets <- initSession opts
@@ -200,19 +233,34 @@ cradleToSession cradle = do
200
233
newHscEnvEq env
201
234
202
235
203
- loadSession :: FilePath -> IO (FilePath -> Action HscEnvEq )
204
- loadSession dir = do
236
+ cradleToSession :: Maybe FilePath -> Cradle a -> Action HscEnvEq
237
+ cradleToSession mbYaml cradle = do
238
+ cmpOpts <- liftIO $ getComponentOptions cradle
239
+ let opts = componentOptions cmpOpts
240
+ deps = componentDependencies cmpOpts
241
+ deps' = case mbYaml of
242
+ -- For direct cradles, the hie.yaml file itself must be watched.
243
+ Just yaml | isDirectCradle cradle -> yaml : deps
244
+ _ -> deps
245
+ existingDeps <- filterM doesFileExist deps'
246
+ need existingDeps
247
+ useNoFile_ $ GetHscEnv opts deps
248
+
249
+
250
+ loadSession :: FilePath -> Action (FilePath -> Action HscEnvEq )
251
+ loadSession dir = liftIO $ do
205
252
cradleLoc <- memoIO $ \ v -> do
206
253
res <- findCradle v
207
254
-- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path
208
255
-- try and normalise that
209
256
-- e.g. see https://github.com/digital-asset/ghcide/issues/126
210
- res' <- traverse makeAbsolute res
257
+ res' <- traverse IO. makeAbsolute res
211
258
return $ normalise <$> res'
212
- session <- memoIO $ \ file -> do
213
- c <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle file
214
- cradleToSession c
215
- return $ \ file -> liftIO $ session =<< cradleLoc file
259
+ let session :: Maybe FilePath -> Action HscEnvEq
260
+ session file = do
261
+ c <- liftIO $ maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle file
262
+ cradleToSession file c
263
+ return $ \ file -> session =<< liftIO (cradleLoc file)
216
264
217
265
218
266
-- | Memoize an IO function, with the characteristics:
0 commit comments