@@ -8,6 +8,7 @@ module Main(main) where
8
8
import Arguments
9
9
import Control.Concurrent.Extra
10
10
import Control.Monad.Extra
11
+ import Control.Exception.Safe
11
12
import Control.Lens ( (^.) )
12
13
import Data.Default
13
14
import Data.List.Extra
@@ -29,7 +30,7 @@ import Development.IDE.Types.Options
29
30
import Development.IDE.Types.Logger
30
31
import Development.IDE.Plugin
31
32
import Development.IDE.Plugin.Test as Test
32
- import Development.IDE.Session (loadSession )
33
+ import Development.IDE.Session (loadSession , setInitialDynFlags , getHieDbLoc , runWithDb )
33
34
import Development.Shake (ShakeOptions (shakeThreads ))
34
35
import qualified Language.Haskell.LSP.Core as LSP
35
36
import Language.Haskell.LSP.Messages
@@ -58,6 +59,8 @@ import Development.IDE.Plugin.HLS.GhcIde as GhcIde
58
59
import Ide.Plugin.Config
59
60
import Ide.PluginUtils (allLspCmdIds' , getProcessID , pluginDescToIdePlugins )
60
61
62
+ import HieDb.Run (Options (.. ), runCommand )
63
+
61
64
ghcideVersion :: IO String
62
65
ghcideVersion = do
63
66
path <- getExecutablePath
@@ -78,13 +81,30 @@ main = do
78
81
if argsVersion then ghcideVersion >>= putStrLn >> exitSuccess
79
82
else hPutStrLn stderr {- see WARNING above -} =<< ghcideVersion
80
83
84
+ whenJust argsCwd IO. setCurrentDirectory
85
+
86
+
87
+ dir <- IO. getCurrentDirectory
88
+ dbLoc <- getHieDbLoc dir
89
+
90
+ case argFilesOrCmd of
91
+ DbCmd opts cmd -> do
92
+ mlibdir <- setInitialDynFlags
93
+ case mlibdir of
94
+ Nothing -> exitWith $ ExitFailure 1
95
+ Just libdir ->
96
+ runCommand libdir opts{database = dbLoc} cmd
97
+ Typecheck (Just -> argFilesOrCmd) | not argLSP -> runWithDb dbLoc $ runIde Arguments {.. }
98
+ _ -> let argFilesOrCmd = Nothing in runWithDb dbLoc $ runIde Arguments {.. }
99
+
100
+
101
+ runIde :: Arguments' (Maybe [FilePath ]) -> HieDb -> IndexQueue -> IO ()
102
+ runIde Arguments {.. } hiedb hiechan = do
81
103
-- lock to avoid overlapping output on stdout
82
104
lock <- newLock
83
105
let logger p = Logger $ \ pri msg -> when (pri >= p) $ withLock lock $
84
106
T. putStrLn $ T. pack (" [" ++ upper (show pri) ++ " ] " ) <> msg
85
107
86
- whenJust argsCwd IO. setCurrentDirectory
87
-
88
108
dir <- IO. getCurrentDirectory
89
109
90
110
let hlsPlugins = pluginDescToIdePlugins $
@@ -107,14 +127,22 @@ main = do
107
127
options = def { LSP. executeCommandCommands = Just hlsCommands
108
128
, LSP. completionTriggerCharacters = Just " ."
109
129
}
110
-
111
- if argLSP then do
130
+ case argFilesOrCmd of
131
+ Nothing -> do
112
132
t <- offsetTime
113
133
hPutStrLn stderr " Starting LSP server..."
114
134
hPutStrLn stderr " If you are seeing this in a terminal, you probably should have run ghcide WITHOUT the --lsp option!"
115
135
runLanguageServer options (pluginHandler plugins) onInitialConfiguration onConfigurationChange $ \ getLspId event vfs caps wProg wIndefProg getConfig rootPath -> do
116
136
t <- t
117
137
hPutStrLn stderr $ " Started LSP server in " ++ showDuration t
138
+
139
+ -- We want to set the global DynFlags right now, so that we can use
140
+ -- `unsafeGlobalDynFlags` even before the project is configured
141
+ -- We do it here since haskell-lsp changes our working directory to the correct place ('rootPath')
142
+ -- before calling this function
143
+ _mlibdir <- setInitialDynFlags
144
+ `catchAny` (\ e -> (hPutStrLn stderr $ " setInitialDynFlags: " ++ displayException e) >> pure Nothing )
145
+
118
146
sessionLoader <- loadSession $ fromMaybe dir rootPath
119
147
config <- fromMaybe def <$> getConfig
120
148
let options = defOptions
@@ -138,8 +166,8 @@ main = do
138
166
unless argsDisableKick $
139
167
action kick
140
168
initialise caps rules
141
- getLspId event wProg wIndefProg (logger logLevel) debouncer options vfs
142
- else do
169
+ getLspId event wProg wIndefProg (logger logLevel) debouncer options vfs hiedb hiechan
170
+ Just argFiles -> do
143
171
-- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error
144
172
hSetEncoding stdout utf8
145
173
hSetEncoding stderr utf8
@@ -174,7 +202,7 @@ main = do
174
202
}
175
203
defOptions = defaultIdeOptions sessionLoader
176
204
logLevel = if argsVerbose then minBound else Info
177
- ide <- initialise def mainRule (pure $ IdInt 0 ) (showEvent lock) dummyWithProg (const (const id )) (logger logLevel) debouncer options vfs
205
+ ide <- initialise def mainRule (pure $ IdInt 0 ) (showEvent lock) dummyWithProg (const (const id )) (logger logLevel) debouncer options vfs hiedb hiechan
178
206
179
207
putStrLn " \n Step 4/4: Type checking the files"
180
208
setFilesOfInterest ide $ HashMap. fromList $ map ((, OnDisk ) . toNormalizedFilePath') files
@@ -203,7 +231,7 @@ main = do
203
231
204
232
unless (null failed) (exitWith $ ExitFailure (length failed))
205
233
206
- {-# ANN main ("HLint: ignore Use nubOrd" :: String) #-}
234
+ {-# ANN runIde ("HLint: ignore Use nubOrd" :: String) #-}
207
235
208
236
expandFiles :: [FilePath ] -> IO [FilePath ]
209
237
expandFiles = concatMapM $ \ x -> do
0 commit comments