@@ -8,6 +8,7 @@ module Main(main) where
88import Arguments
99import Control.Concurrent.Extra
1010import Control.Monad.Extra
11+ import Control.Exception.Safe
1112import Control.Lens ( (^.) )
1213import Data.Default
1314import Data.List.Extra
@@ -29,7 +30,7 @@ import Development.IDE.Types.Options
2930import Development.IDE.Types.Logger
3031import Development.IDE.Plugin
3132import Development.IDE.Plugin.Test as Test
32- import Development.IDE.Session (loadSession )
33+ import Development.IDE.Session (loadSession , setInitialDynFlags , getHieDbLoc , runWithDb )
3334import Development.Shake (ShakeOptions (shakeThreads ))
3435import qualified Language.Haskell.LSP.Core as LSP
3536import Language.Haskell.LSP.Messages
@@ -58,6 +59,8 @@ import Development.IDE.Plugin.HLS.GhcIde as GhcIde
5859import Ide.Plugin.Config
5960import Ide.PluginUtils (allLspCmdIds' , getProcessID , pluginDescToIdePlugins )
6061
62+ import HieDb.Run (Options (.. ), runCommand )
63+
6164ghcideVersion :: IO String
6265ghcideVersion = do
6366 path <- getExecutablePath
@@ -78,13 +81,30 @@ main = do
7881 if argsVersion then ghcideVersion >>= putStrLn >> exitSuccess
7982 else hPutStrLn stderr {- see WARNING above -} =<< ghcideVersion
8083
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
81103 -- lock to avoid overlapping output on stdout
82104 lock <- newLock
83105 let logger p = Logger $ \ pri msg -> when (pri >= p) $ withLock lock $
84106 T. putStrLn $ T. pack (" [" ++ upper (show pri) ++ " ] " ) <> msg
85107
86- whenJust argsCwd IO. setCurrentDirectory
87-
88108 dir <- IO. getCurrentDirectory
89109
90110 let hlsPlugins = pluginDescToIdePlugins $
@@ -107,14 +127,22 @@ main = do
107127 options = def { LSP. executeCommandCommands = Just hlsCommands
108128 , LSP. completionTriggerCharacters = Just " ."
109129 }
110-
111- if argLSP then do
130+ case argFilesOrCmd of
131+ Nothing -> do
112132 t <- offsetTime
113133 hPutStrLn stderr " Starting LSP server..."
114134 hPutStrLn stderr " If you are seeing this in a terminal, you probably should have run ghcide WITHOUT the --lsp option!"
115135 runLanguageServer options (pluginHandler plugins) onInitialConfiguration onConfigurationChange $ \ getLspId event vfs caps wProg wIndefProg getConfig rootPath -> do
116136 t <- t
117137 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+
118146 sessionLoader <- loadSession $ fromMaybe dir rootPath
119147 config <- fromMaybe def <$> getConfig
120148 let options = defOptions
@@ -138,8 +166,8 @@ main = do
138166 unless argsDisableKick $
139167 action kick
140168 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
143171 -- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error
144172 hSetEncoding stdout utf8
145173 hSetEncoding stderr utf8
@@ -174,7 +202,7 @@ main = do
174202 }
175203 defOptions = defaultIdeOptions sessionLoader
176204 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
178206
179207 putStrLn " \n Step 4/4: Type checking the files"
180208 setFilesOfInterest ide $ HashMap. fromList $ map ((, OnDisk ) . toNormalizedFilePath') files
@@ -203,7 +231,7 @@ main = do
203231
204232 unless (null failed) (exitWith $ ExitFailure (length failed))
205233
206- {-# ANN main ("HLint: ignore Use nubOrd" :: String) #-}
234+ {-# ANN runIde ("HLint: ignore Use nubOrd" :: String) #-}
207235
208236expandFiles :: [FilePath ] -> IO [FilePath ]
209237expandFiles = concatMapM $ \ x -> do
0 commit comments