22-- SPDX-License-Identifier: Apache-2.0
33{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
44{-# LANGUAGE TemplateHaskell #-}
5- {-# LANGUAGE CPP #-}
6- #include "ghc-api-version.h"
75
86module Main (main ) where
97
@@ -31,7 +29,7 @@ import Development.IDE.Types.Options
3129import Development.IDE.Types.Logger
3230import Development.IDE.Plugin
3331import Development.IDE.Plugin.Test as Test
34- import Development.IDE.Session (loadSession , cacheDir )
32+ import Development.IDE.Session (loadSession , setInitialDynFlags , getHieDbLoc , runWithDb )
3533import qualified Language.Haskell.LSP.Core as LSP
3634import Language.Haskell.LSP.Messages
3735import Language.Haskell.LSP.Types
@@ -59,24 +57,8 @@ import Development.IDE.Plugin.HLS.GhcIde as GhcIde
5957import Ide.Plugin.Config
6058import Ide.PluginUtils (allLspCmdIds' , getProcessID , pluginDescToIdePlugins )
6159
62- import HieDb.Create
63- import HieDb.Types
64- import HieDb.Utils
65- import Database.SQLite.Simple
66- import qualified Data.ByteString.Char8 as B
67- import qualified Crypto.Hash.SHA1 as H
68- import Control.Concurrent.Async
69- import Control.Concurrent.STM.TQueue
70- import Control.Concurrent.STM (atomically )
71- import Control.Exception
72- import System.Directory
73- import Data.ByteString.Base16
60+ import HieDb.Types (LibDir (.. ))
7461import HieDb.Run (Options (.. ), runCommand )
75- import Maybes (MaybeT (runMaybeT ))
76- import HIE.Bios.Types (CradleLoadResult (.. ))
77- import HIE.Bios.Environment (getRuntimeGhcLibDir )
78- import DynFlags
79-
8062
8163ghcideVersion :: IO String
8264ghcideVersion = do
@@ -89,30 +71,6 @@ ghcideVersion = do
8971 <> " ) (PATH: " <> path <> " )"
9072 <> gitHashSection
9173
92- -- | Wraps `withHieDb` to provide a database connection for reading, and a `HieWriterChan` for
93- -- writing. Actions are picked off one by one from the `HieWriterChan` and executed in serial
94- -- by a worker thread using a dedicated database connection.
95- -- This is done in order to serialize writes to the database, or else SQLite becomes unhappy
96- runWithDb :: FilePath -> (HieDb -> IndexQueue -> IO () ) -> IO ()
97- runWithDb fp k =
98- withHieDb fp $ \ writedb -> do
99- initConn writedb
100- chan <- newTQueueIO
101- race_ (writerThread writedb chan) (withHieDb fp (flip k chan))
102- where
103- writerThread db chan = forever $ do
104- k <- atomically $ readTQueue chan
105- k db `catch` \ e@ SQLError {} -> do
106- hPutStrLn stderr $ " Error in worker, ignoring: " ++ show e
107-
108- getHieDbLoc :: FilePath -> IO FilePath
109- getHieDbLoc dir = do
110- let db = dirHash++ " -" ++ takeBaseName dir++ " -" ++ VERSION_ghc <.> " hiedb"
111- dirHash = B. unpack $ encode $ H. hash $ B. pack dir
112- cDir <- IO. getXdgDirectory IO. XdgCache cacheDir
113- createDirectoryIfMissing True cDir
114- pure (cDir </> db)
115-
11674main :: IO ()
11775main = do
11876 -- WARNING: If you write to stdout before runLanguageServer
@@ -126,19 +84,10 @@ main = do
12684
12785 -- We want to set the global DynFlags right now, so that we can use
12886 -- `unsafeGlobalDynFlags` even before the project is configured
87+ libdir <- setInitialDynFlags
88+
12989 dir <- IO. getCurrentDirectory
13090 dbLoc <- getHieDbLoc dir
131- hieYaml <- runMaybeT $ yamlConfig dir
132- cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle hieYaml
133- libDirRes <- getRuntimeGhcLibDir cradle
134- libdir <- case libDirRes of
135- CradleSuccess libdir -> pure $ Just libdir
136- CradleFail err -> do
137- hPutStrLn stderr $ " Couldn't load cradle for libdir: " ++ show err
138- return Nothing
139- CradleNone -> return Nothing
140- dynFlags <- mapM (dynFlagsForPrinting . LibDir ) libdir
141- mapM_ setUnsafeGlobalDynFlags dynFlags
14291
14392 case argFilesOrCmd of
14493 DbCmd cmd -> do
0 commit comments