8
8
module Main (main ) where
9
9
10
10
import Arguments
11
- import Data.Binary (Binary )
12
- import Data.Dynamic (Typeable )
13
- import Data.Hashable (Hashable )
11
+ import Data.Functor ((<&>) )
14
12
import Data.Maybe
15
13
import Data.List.Extra
16
14
import System.FilePath
17
15
import Control.Concurrent.Extra
18
- import Control.DeepSeq (NFData )
19
16
import Control.Exception
20
17
import Control.Monad.Extra
21
18
import Control.Monad.IO.Class
@@ -53,19 +50,19 @@ import System.IO
53
50
import System.Exit
54
51
import Paths_ghcide
55
52
import Development.GitRev
56
- import Development.Shake (Action , RuleResult , Rules , action , doesFileExist , need )
53
+ import Development.Shake (doesDirectoryExist , Action , Rules , action , doesFileExist , need )
57
54
import qualified Data.HashSet as HashSet
58
55
import qualified Data.Map.Strict as Map
59
56
60
57
import GHC hiding (def )
61
- import GHC.Generics (Generic )
62
58
import qualified GHC.Paths
63
59
import DynFlags
64
60
65
61
import HIE.Bios.Environment
66
62
import HIE.Bios
67
63
import HIE.Bios.Cradle
68
64
import HIE.Bios.Types
65
+ import RuleTypes
69
66
70
67
-- Prefix for the cache path
71
68
cacheDir :: String
@@ -127,7 +124,7 @@ main = do
127
124
, optShakeProfiling = argsShakeProfiling
128
125
}
129
126
debouncer <- newAsyncDebouncer
130
- initialise caps (loadGhcSessionIO >> mainRule >> pluginRules plugins >> action kick)
127
+ initialise caps (cradleRules >> mainRule >> pluginRules plugins >> action kick)
131
128
getLspId event (logger minBound ) debouncer options vfs
132
129
else do
133
130
putStrLn $ " Ghcide setup tester in " ++ dir ++ " ."
@@ -164,7 +161,7 @@ main = do
164
161
let options =
165
162
(defaultIdeOptions $ return $ return . grab)
166
163
{ optShakeProfiling = argsShakeProfiling }
167
- ide <- initialise def (loadGhcSessionIO >> mainRule) (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
164
+ ide <- initialise def (cradleRules >> mainRule) (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
168
165
169
166
putStrLn " \n Step 6/6: Type checking the files"
170
167
setFilesOfInterest ide $ HashSet. fromList $ map toNormalizedFilePath files
@@ -178,6 +175,10 @@ main = do
178
175
179
176
unless (null failed) exitFailure
180
177
178
+ cradleRules :: Rules ()
179
+ cradleRules = do
180
+ loadGhcSessionIO
181
+ cradleToSession
181
182
182
183
expandFiles :: [FilePath ] -> IO [FilePath ]
183
184
expandFiles = concatMapM $ \ x -> do
@@ -204,20 +205,6 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath -> file) diags) =
204
205
withLock lock $ T. putStrLn $ showDiagnosticsColored $ map (file,ShowDiag ,) diags
205
206
showEvent lock e = withLock lock $ print e
206
207
207
-
208
- -- Rule type for caching GHC sessions.
209
- type instance RuleResult GetHscEnv = HscEnvEq
210
-
211
- data GetHscEnv = GetHscEnv
212
- { hscenvOptions :: [String ] -- componentOptions from hie-bios
213
- , hscenvDependencies :: [FilePath ] -- componentDependencies from hie-bios
214
- }
215
- deriving (Eq , Show , Typeable , Generic )
216
- instance Hashable GetHscEnv
217
- instance NFData GetHscEnv
218
- instance Binary GetHscEnv
219
-
220
-
221
208
loadGhcSessionIO :: Rules ()
222
209
loadGhcSessionIO =
223
210
-- This rule is for caching the GHC session. E.g., even when the cabal file
@@ -226,10 +213,10 @@ loadGhcSessionIO =
226
213
defineNoFile $ \ (GetHscEnv opts deps) ->
227
214
liftIO $ createSession $ ComponentOptions opts deps
228
215
229
-
230
216
getComponentOptions :: Cradle a -> IO ComponentOptions
231
217
getComponentOptions cradle = do
232
218
let showLine s = putStrLn (" > " ++ s)
219
+ -- WARNING 'runCradle is very expensive and must be called as few times as possible
233
220
cradleRes <- runCradle (cradleOptsProg cradle) showLine " "
234
221
case cradleRes of
235
222
CradleSuccess r -> pure r
@@ -285,8 +272,14 @@ setHiDir f d =
285
272
-- override user settings to avoid conflicts leading to recompilation
286
273
d { hiDir = Just f}
287
274
288
- cradleToSession :: Maybe FilePath -> Cradle a -> Action HscEnvEq
289
- cradleToSession mbYaml cradle = do
275
+ cradleToSession :: Rules ()
276
+ cradleToSession = define $ \ LoadCradle nfp -> do
277
+ let f = fromNormalizedFilePath nfp
278
+
279
+ -- If the path points to a directory, load the implicit cradle
280
+ mbYaml <- doesDirectoryExist f <&> \ isDir -> if isDir then Nothing else Just f
281
+ cradle <- liftIO $ maybe (loadImplicitCradle $ addTrailingPathSeparator f) loadCradle mbYaml
282
+
290
283
cmpOpts <- liftIO $ getComponentOptions cradle
291
284
let opts = componentOptions cmpOpts
292
285
deps = componentDependencies cmpOpts
@@ -296,7 +289,7 @@ cradleToSession mbYaml cradle = do
296
289
_ -> deps
297
290
existingDeps <- filterM doesFileExist deps'
298
291
need existingDeps
299
- useNoFile_ $ GetHscEnv opts deps
292
+ ( [] ,) . pure <$> useNoFile_ ( GetHscEnv opts deps)
300
293
301
294
302
295
loadSession :: FilePath -> Action (FilePath -> Action HscEnvEq )
@@ -310,8 +303,9 @@ loadSession dir = liftIO $ do
310
303
return $ normalise <$> res'
311
304
let session :: Maybe FilePath -> Action HscEnvEq
312
305
session file = do
313
- c <- liftIO $ maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle file
314
- cradleToSession file c
306
+ -- In the absence of a cradle file, just pass the directory from where to calculate an implicit cradle
307
+ let cradle = toNormalizedFilePath $ fromMaybe dir file
308
+ use_ LoadCradle cradle
315
309
return $ \ file -> session =<< liftIO (cradleLoc file)
316
310
317
311
0 commit comments