@@ -39,6 +39,7 @@ import System.Exit
39
39
import Paths_ghcide
40
40
import Development.Shake hiding (Env )
41
41
import qualified Data.Set as Set
42
+ import qualified Data.Map.Strict as Map
42
43
43
44
import GHC hiding (def )
44
45
import qualified GHC.Paths
@@ -64,45 +65,56 @@ main = do
64
65
65
66
-- lock to avoid overlapping output on stdout
66
67
lock <- newLock
67
- let logger = Logger $ \ pri msg -> withLock lock $
68
+ let logger p = Logger $ \ pri msg -> when (pri >= p) $ withLock lock $
68
69
T. putStrLn $ T. pack (" [" ++ upper (show pri) ++ " ] " ) <> msg
69
70
70
71
whenJust argsCwd setCurrentDirectory
71
72
72
73
dir <- getCurrentDirectory
73
- hPutStrLn stderr dir
74
74
75
75
if argLSP then do
76
76
t <- offsetTime
77
77
hPutStrLn stderr " Starting LSP server..."
78
78
runLanguageServer def def $ \ event vfs caps -> do
79
79
t <- t
80
80
hPutStrLn stderr $ " Started LSP server in " ++ showDuration t
81
- let options = (defaultIdeOptions $ loadEnvironment dir)
81
+ -- very important we only call loadSession once, and it's fast, so just do it before starting
82
+ session <- loadSession dir
83
+ let options = (defaultIdeOptions $ return session)
82
84
{ optReportProgress = clientSupportsProgress caps }
83
- initialise (mainRule >> action kick) event logger options vfs
85
+ initialise (mainRule >> action kick) event ( logger minBound ) options vfs
84
86
else do
85
- -- Note that this whole section needs to change once we have genuine
86
- -- multi environment support. Needs rewriting in terms of loadEnvironment.
87
- putStrLn " [1/6] Finding hie-bios cradle"
88
- cradle <- getCradle dir
89
- print cradle
87
+ putStrLn $ " Ghcide setup tester in " ++ dir ++ " ."
88
+ putStrLn " Report bugs at https://github.com/digital-asset/ghcide/issues"
90
89
91
- putStrLn " \n [2/6] Converting Cradle to GHC session"
92
- env <- newSession' cradle
93
-
94
- putStrLn " \n [3/6] Initialising IDE session"
95
- vfs <- makeVFSHandle
96
- ide <- initialise mainRule (showEvent lock) logger (defaultIdeOptions $ return $ const $ return env) vfs
97
-
98
- putStrLn " \n [4/6] Finding interesting files"
90
+ putStrLn $ " \n Step 1/6: Finding files to test in " ++ dir
99
91
files <- nubOrd <$> expandFiles (argFiles ++ [" ." | null argFiles])
100
92
putStrLn $ " Found " ++ show (length files) ++ " files"
101
93
102
- putStrLn " \n [5/6] Setting interesting files"
94
+ putStrLn " \n Step 2/6: Looking for hie.yaml files that control setup"
95
+ cradles <- mapM findCradle files
96
+ let ucradles = nubOrd cradles
97
+ let n = length ucradles
98
+ putStrLn $ " Found " ++ show n ++ " cradle" ++ [' s' | n /= 1 ]
99
+ sessions <- forM (zipFrom (1 :: Int ) ucradles) $ \ (i, x) -> do
100
+ let msg = maybe (" Implicit cradle for " ++ dir) (" Loading " ++ ) x
101
+ putStrLn $ " \n Step 3/6, Cradle " ++ show i ++ " /" ++ show n ++ " : " ++ msg
102
+ cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle x
103
+ when (isNothing x) $ print cradle
104
+ putStrLn $ " \n Step 4/6, Cradle " ++ show i ++ " /" ++ show n ++ " : Loading GHC Session"
105
+ cradleToSession cradle
106
+
107
+ putStrLn " \n Step 5/6: Initializing the IDE"
108
+ vfs <- makeVFSHandle
109
+ let cradlesToSessions = Map. fromList $ zip ucradles sessions
110
+ let filesToCradles = Map. fromList $ zip files cradles
111
+ let grab file = fromMaybe (head sessions) $ do
112
+ cradle <- Map. lookup file filesToCradles
113
+ Map. lookup cradle cradlesToSessions
114
+ ide <- initialise mainRule (showEvent lock) (logger Info ) (defaultIdeOptions $ return $ return . grab) vfs
115
+
116
+ putStrLn " \n Step 6/6: Type checking the files"
103
117
setFilesOfInterest ide $ Set. fromList $ map toNormalizedFilePath files
104
-
105
- putStrLn " \n [6/6] Loading interesting files"
106
118
results <- runActionSync ide $ uses TypeCheck $ map toNormalizedFilePath files
107
119
let (worked, failed) = partition fst $ zip (map isJust results) files
108
120
putStrLn $ " Files that worked: " ++ show (length worked)
@@ -137,8 +149,9 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath -> file) diags) =
137
149
withLock lock $ T. putStrLn $ showDiagnosticsColored $ map (file,) diags
138
150
showEvent lock e = withLock lock $ print e
139
151
140
- newSession' :: Cradle -> IO HscEnvEq
141
- newSession' cradle = do
152
+
153
+ cradleToSession :: Cradle -> IO HscEnvEq
154
+ cradleToSession cradle = do
142
155
opts <- either throwIO return =<< getCompilerOptions " " cradle
143
156
libdir <- getLibdir
144
157
env <- runGhc (Just libdir) $ do
@@ -147,15 +160,33 @@ newSession' cradle = do
147
160
initDynLinker env
148
161
newHscEnvEq env
149
162
150
- loadEnvironment :: FilePath -> IO (FilePath -> Action HscEnvEq )
151
- loadEnvironment dir = do
152
- res <- liftIO $ newSession' =<< getCradle dir
153
- return $ const $ return res
154
-
155
- getCradle :: FilePath -> IO Cradle
156
- getCradle dir = do
157
- dir <- pure $ addTrailingPathSeparator dir
158
- mbYaml <- findCradle dir
159
- case mbYaml of
160
- Nothing -> loadImplicitCradle dir
161
- Just yaml -> loadCradle yaml
163
+
164
+ loadSession :: FilePath -> IO (FilePath -> Action HscEnvEq )
165
+ loadSession dir = do
166
+ cradleLoc <- memoIO $ \ v -> do
167
+ res <- findCradle v
168
+ -- Sometimes we get C: and sometimes we get c:, try and normalise that
169
+ -- e.g. see https://github.com/digital-asset/ghcide/issues/126
170
+ return $ normalise <$> res
171
+ session <- memoIO $ \ file -> do
172
+ c <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle file
173
+ cradleToSession c
174
+ return $ \ file -> liftIO $ session =<< cradleLoc file
175
+
176
+
177
+ -- | Memoize an IO function, with the characteristics:
178
+ --
179
+ -- * If multiple people ask for a result simultaneously, make sure you only compute it once.
180
+ --
181
+ -- * If there are exceptions, repeatedly reraise them.
182
+ --
183
+ -- * If the caller is aborted (async exception) finish computing it anyway.
184
+ memoIO :: Ord a => (a -> IO b ) -> IO (a -> IO b )
185
+ memoIO op = do
186
+ ref <- newVar Map. empty
187
+ return $ \ k -> join $ mask_ $ modifyVar ref $ \ mp ->
188
+ case Map. lookup k mp of
189
+ Nothing -> do
190
+ res <- onceFork $ op k
191
+ return (Map. insert k res mp, res)
192
+ Just res -> return (mp, res)
0 commit comments