11-- Copyright (c) 2019 The DAML Authors. All rights reserved.
22-- SPDX-License-Identifier: Apache-2.0
33{-# OPTIONS_GHC -Wno-dodgy-imports #-} -- GHC no longer exports def in GHC 8.6 and above
4+ {-# LANGUAGE DeriveGeneric #-}
5+ {-# LANGUAGE OverloadedStrings #-}
46{-# LANGUAGE RecordWildCards #-}
5- {-# LANGUAGE ViewPatterns #-}
67{-# LANGUAGE TupleSections #-}
7- {-# LANGUAGE OverloadedStrings #-}
8+ {-# LANGUAGE TypeFamilies #-}
9+ {-# LANGUAGE ViewPatterns #-}
810
911module Main (main ) where
1012
@@ -14,11 +16,14 @@ import Control.Exception
1416import Control.Monad.Extra
1517import Control.Monad.IO.Class
1618import Data.Default
19+ import qualified Data.HashSet as HashSet
1720import Data.List.Extra
1821import qualified Data.Map.Strict as Map
1922import Data.Maybe
2023import qualified Data.Text as T
2124import qualified Data.Text.IO as T
25+ -- import Data.Version
26+ -- import Development.GitRev
2227import Development.IDE.Core.Debouncer
2328import Development.IDE.Core.FileStore
2429import Development.IDE.Core.OfInterest
@@ -34,44 +39,83 @@ import Development.IDE.Types.Diagnostics
3439import Development.IDE.Types.Location
3540import Development.IDE.Types.Logger
3641import Development.IDE.Types.Options
37- import Development.Shake (Action , action )
38- import GHC hiding (def )
42+ import Development.Shake (Action , Rules , action )
3943import HIE.Bios
40- import Ide.Plugin.Formatter
44+ import qualified Language.Haskell.LSP.Core as LSP
45+ import Ide.Logger
46+ import Ide.Plugin
4147import Ide.Plugin.Config
4248import Language.Haskell.LSP.Messages
4349import Language.Haskell.LSP.Types (LspId (IdInt ))
44- import Linker
45- import qualified Data.HashSet as HashSet
46- import System.Directory.Extra as IO
50+ import RuleTypes
51+ import Rules
52+ import qualified System.Directory.Extra as IO
53+ -- import System.Environment
4754import System.Exit
4855import System.FilePath
4956import System.IO
57+ import System.Log.Logger as L
5058import System.Time.Extra
5159
5260-- ---------------------------------------------------------------------
5361
5462import Development.IDE.Plugin.CodeAction as CodeAction
5563import Development.IDE.Plugin.Completions as Completions
5664import Ide.Plugin.Example as Example
65+ import Ide.Plugin.Example2 as Example2
5766import Ide.Plugin.Floskell as Floskell
5867import Ide.Plugin.Ormolu as Ormolu
68+ import Ide.Plugin.Pragmas as Pragmas
5969
6070-- ---------------------------------------------------------------------
6171
62- -- The plugins configured for use in this instance of the language
72+ -- | The plugins configured for use in this instance of the language
6373-- server.
6474-- These can be freely added or removed to tailor the available
6575-- features of the server.
66- idePlugins :: Bool -> Plugin Config
67- idePlugins includeExample
68- = Completions. plugin <>
69- CodeAction. plugin <>
70- formatterPlugins [(" ormolu" , Ormolu. provider)
71- ,(" floskell" , Floskell. provider)] <>
72- if includeExample then Example. plugin else mempty
76+ idePlugins :: T. Text -> Bool -> (Plugin Config , [T. Text ])
77+ idePlugins pid includeExamples
78+ = (asGhcIdePlugin ps, allLspCmdIds' pid ps)
79+ where
80+ ps = pluginDescToIdePlugins allPlugins
81+ allPlugins = if includeExamples
82+ then basePlugins ++ examplePlugins
83+ else basePlugins
84+ basePlugins =
85+ [
86+ -- applyRefactDescriptor "applyrefact"
87+ -- , brittanyDescriptor "brittany"
88+ -- , haddockDescriptor "haddock"
89+ -- -- , hareDescriptor "hare"
90+ -- , hsimportDescriptor "hsimport"
91+ -- , liquidDescriptor "liquid"
92+ -- , packageDescriptor "package"
93+ Pragmas. descriptor " pragmas"
94+ , Floskell. descriptor " floskell"
95+ -- , genericDescriptor "generic"
96+ -- , ghcmodDescriptor "ghcmod"
97+ , Ormolu. descriptor " ormolu"
98+ ]
99+ examplePlugins =
100+ [Example. descriptor " eg"
101+ ,Example2. descriptor " eg2"
102+ -- ,hfaAlignDescriptor "hfaa"
103+ ]
104+
73105
74106-- ---------------------------------------------------------------------
107+ -- Prefix for the cache path
108+ {-
109+ cacheDir :: String
110+ cacheDir = "ghcide"
111+
112+ getCacheDir :: [String] -> IO FilePath
113+ getCacheDir opts = IO.getXdgDirectory IO.XdgCache (cacheDir </> opts_hash)
114+ where
115+ -- Create a unique folder per set of different GHC options, assuming that each different set of
116+ -- GHC options will create incompatible interface files.
117+ opts_hash = B.unpack $ encode $ H.finalize $ H.updates H.init (map B.pack opts)
118+ -}
75119
76120main :: IO ()
77121main = do
@@ -82,40 +126,57 @@ main = do
82126 if argsVersion then ghcideVersion >>= putStrLn >> exitSuccess
83127 else hPutStrLn stderr {- see WARNING above -} =<< ghcideVersion
84128
129+ -- LSP.setupLogger (optLogFile opts) ["hie", "hie-bios"]
130+ -- $ if optDebugOn opts then L.DEBUG else L.INFO
131+ LSP. setupLogger argsLogFile [" hie" , " hie-bios" ]
132+ $ if argsDebugOn then L. DEBUG else L. INFO
133+
85134 -- lock to avoid overlapping output on stdout
86135 lock <- newLock
87136 let logger p = Logger $ \ pri msg -> when (pri >= p) $ withLock lock $
88137 T. putStrLn $ T. pack (" [" ++ upper (show pri) ++ " ] " ) <> msg
89138
90- whenJust argsCwd setCurrentDirectory
139+ whenJust argsCwd IO. setCurrentDirectory
91140
92- dir <- getCurrentDirectory
141+ dir <- IO. getCurrentDirectory
93142
94- let plugins = idePlugins argsExamplePlugin
143+ pid <- getPid
144+ let
145+ -- (ps, commandIds) = idePlugins pid argsExamplePlugin
146+ (ps, commandIds) = idePlugins pid True
147+ plugins = Completions. plugin <> CodeAction. plugin <>
148+ ps
149+ options = def { LSP. executeCommandCommands = Just commandIds
150+ , LSP. completionTriggerCharacters = Just " ."
151+ }
95152
96153 if argLSP then do
97154 t <- offsetTime
98155 hPutStrLn stderr " Starting (haskell-language-server)LSP server..."
99156 hPutStrLn stderr " If you are seeing this in a terminal, you probably should have run ghcide WITHOUT the --lsp option!"
100- runLanguageServer def (pluginHandler plugins) getInitialConfig getConfigFromNotification $ \ getLspId event vfs caps -> do
157+ runLanguageServer options (pluginHandler plugins) getInitialConfig getConfigFromNotification $ \ getLspId event vfs caps -> do
101158 t <- t
102159 hPutStrLn stderr $ " Started LSP server in " ++ showDuration t
103- -- very important we only call loadSession once, and it's fast, so just do it before starting
104- session <- loadSession dir
105- let options = (defaultIdeOptions $ return session)
160+ let options = (defaultIdeOptions $ loadSession dir)
106161 { optReportProgress = clientSupportsProgress caps
107162 , optShakeProfiling = argsShakeProfiling
163+ , optTesting = argsTesting
108164 }
109165 debouncer <- newAsyncDebouncer
110- initialise caps (mainRule >> pluginRules plugins >> action kick) getLspId event (logger minBound ) debouncer options vfs
166+ initialise caps (cradleRules >> mainRule >> pluginRules plugins >> action kick)
167+ getLspId event hlsLogger debouncer options vfs
111168 else do
169+ -- GHC produces messages with UTF8 in them, so make sure the terminal doesn't error
170+ hSetEncoding stdout utf8
171+ hSetEncoding stderr utf8
172+
112173 putStrLn $ " (haskell-language-server)Ghcide setup tester in " ++ dir ++ " ."
113174 putStrLn " Report bugs at https://github.com/haskell/haskell-language-server/issues"
114175
115176 putStrLn $ " \n Step 1/6: Finding files to test in " ++ dir
116177 files <- expandFiles (argFiles ++ [" ." | null argFiles])
117178 -- LSP works with absolute file paths, so try and behave similarly
118- files <- nubOrd <$> mapM canonicalizePath files
179+ files <- nubOrd <$> mapM IO. canonicalizePath files
119180 putStrLn $ " Found " ++ show (length files) ++ " files"
120181
121182 putStrLn " \n Step 2/6: Looking for hie.yaml files that control setup"
@@ -129,7 +190,8 @@ main = do
129190 cradle <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle x
130191 when (isNothing x) $ print cradle
131192 putStrLn $ " \n Step 4/6, Cradle " ++ show i ++ " /" ++ show n ++ " : Loading GHC Session"
132- cradleToSession cradle
193+ opts <- getComponentOptions cradle
194+ createSession opts
133195
134196 putStrLn " \n Step 5/6: Initializing the IDE"
135197 vfs <- makeVFSHandle
@@ -142,7 +204,7 @@ main = do
142204 let options =
143205 (defaultIdeOptions $ return $ return . grab)
144206 { optShakeProfiling = argsShakeProfiling }
145- ide <- initialise def mainRule (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
207+ ide <- initialise def (cradleRules >> mainRule) (pure $ IdInt 0 ) (showEvent lock) (logger Info ) noopDebouncer options vfs
146208
147209 putStrLn " \n Step 6/6: Type checking the files"
148210 setFilesOfInterest ide $ HashSet. fromList $ map toNormalizedFilePath files
@@ -156,6 +218,10 @@ main = do
156218
157219 unless (null failed) exitFailure
158220
221+ cradleRules :: Rules ()
222+ cradleRules = do
223+ loadGhcSession
224+ cradleToSession
159225
160226expandFiles :: [FilePath ] -> IO [FilePath ]
161227expandFiles = concatMapM $ \ x -> do
@@ -164,7 +230,7 @@ expandFiles = concatMapM $ \x -> do
164230 let recurse " ." = True
165231 recurse x | " ." `isPrefixOf` takeFileName x = False -- skip .git etc
166232 recurse x = takeFileName x `notElem` [" dist" ," dist-newstyle" ] -- cabal directories
167- files <- filter (\ x -> takeExtension x `elem` [" .hs" ," .lhs" ]) <$> listFilesInside (return . recurse) x
233+ files <- filter (\ x -> takeExtension x `elem` [" .hs" ," .lhs" ]) <$> IO. listFilesInside (return . recurse) x
168234 when (null files) $
169235 fail $ " Couldn't find any .hs/.lhs files inside directory: " ++ x
170236 return files
@@ -182,37 +248,21 @@ showEvent lock (EventFileDiagnostics (toNormalizedFilePath -> file) diags) =
182248 withLock lock $ T. putStrLn $ showDiagnosticsColored $ map (file,ShowDiag ,) diags
183249showEvent lock e = withLock lock $ print e
184250
185-
186- cradleToSession :: Cradle a -> IO HscEnvEq
187- cradleToSession cradle = do
188- cradleRes <- getCompilerOptions " " cradle
189- opts <- case cradleRes of
190- CradleSuccess r -> pure r
191- CradleFail err -> throwIO err
192- -- TODO Rather than failing here, we should ignore any files that use this cradle.
193- -- That will require some more changes.
194- CradleNone -> fail " 'none' cradle is not yet supported"
195- libdir <- getLibdir
196- env <- runGhc (Just libdir) $ do
197- _targets <- initSession opts
198- getSession
199- initDynLinker env
200- newHscEnvEq env
201-
202-
203- loadSession :: FilePath -> IO (FilePath -> Action HscEnvEq )
204- loadSession dir = do
251+ loadSession :: FilePath -> Action (FilePath -> Action HscEnvEq )
252+ loadSession dir = liftIO $ do
205253 cradleLoc <- memoIO $ \ v -> do
206254 res <- findCradle v
207255 -- Sometimes we get C:, sometimes we get c:, and sometimes we get a relative path
208256 -- try and normalise that
209257 -- e.g. see https://github.com/digital-asset/ghcide/issues/126
210- res' <- traverse makeAbsolute res
258+ res' <- traverse IO. makeAbsolute res
211259 return $ normalise <$> res'
212- session <- memoIO $ \ file -> do
213- c <- maybe (loadImplicitCradle $ addTrailingPathSeparator dir) loadCradle file
214- cradleToSession c
215- return $ \ file -> liftIO $ session =<< cradleLoc file
260+ let session :: Maybe FilePath -> Action HscEnvEq
261+ session file = do
262+ -- In the absence of a cradle file, just pass the directory from where to calculate an implicit cradle
263+ let cradle = toNormalizedFilePath $ fromMaybe dir file
264+ use_ LoadCradle cradle
265+ return $ \ file -> session =<< liftIO (cradleLoc file)
216266
217267
218268-- | Memoize an IO function, with the characteristics:
0 commit comments