1
- {-# LANGUAGE RecordWildCards #-}
2
- {-# LANGUAGE NamedFieldPuns #-}
3
- {-# LANGUAGE CPP #-}
1
+ {-# LANGUAGE CPP #-}
2
+ {-# LANGUAGE DataKinds #-}
3
+ {-# LANGUAGE ExplicitNamespaces #-}
4
+ {-# LANGUAGE GeneralizedNewtypeDeriving #-}
5
+ {-# LANGUAGE LambdaCase #-}
6
+ {-# LANGUAGE NamedFieldPuns #-}
7
+ {-# LANGUAGE OverloadedStrings #-}
8
+ {-# LANGUAGE RecordWildCards #-}
9
+ {-# LANGUAGE ScopedTypeVariables #-}
4
10
-- | This module is based on the hie-wrapper.sh script in
5
11
-- https://github.com/alanz/vscode-hie-server
6
12
module Main where
@@ -28,6 +34,28 @@ import qualified Data.Map.Strict as Map
28
34
#else
29
35
import System.Process
30
36
#endif
37
+ import qualified Data.Text.IO as T
38
+ import Control.Monad.Trans.Except (ExceptT , runExceptT , throwE )
39
+ import qualified Data.Text as T
40
+ import Language.LSP.Server (LspM )
41
+ import Control.Monad.IO.Class (MonadIO (liftIO ))
42
+ import Control.Monad.IO.Unlift (MonadUnliftIO )
43
+ import qualified Language.LSP.Server as LSP
44
+ import qualified Development.IDE.Main as Main
45
+ import Ide.Plugin.Config (Config )
46
+ import Language.LSP.Types (RequestMessage , ResponseError , MessageActionItem (MessageActionItem ), Method (Initialize ), MessageType (MtError ), SMethod (SWindowShowMessageRequest , SExit ), ShowMessageRequestParams (ShowMessageRequestParams ))
47
+ import Development.IDE.Types.Logger ( makeDefaultStderrRecorder ,
48
+ cmapWithPrio ,
49
+ Pretty (pretty ),
50
+ Logger (Logger ),
51
+ Priority (Error , Debug , Info , Warning ),
52
+ Recorder (logger_ ),
53
+ WithPriority (WithPriority ) )
54
+ import Data.Maybe
55
+ import GHC.Stack.Types (emptyCallStack )
56
+ import Control.Concurrent (tryPutMVar )
57
+ import Development.IDE.LSP.LanguageServer (runLanguageServer )
58
+ import HIE.Bios.Internal.Log
31
59
32
60
-- ---------------------------------------------------------------------
33
61
@@ -57,9 +85,15 @@ main = do
57
85
cradle <- findProjectCradle' False
58
86
(CradleSuccess libdir) <- HieBios. getRuntimeGhcLibDir cradle
59
87
putStr libdir
60
- _ -> launchHaskellLanguageServer args
88
+ _ -> launchHaskellLanguageServer args >>= \ case
89
+ Right () -> pure ()
90
+ Left err -> do
91
+ T. hPutStrLn stderr (prettyError err NoShorten )
92
+ case args of
93
+ Ghcide _ -> launchErrorLSP (prettyError err Shorten )
94
+ _ -> pure ()
61
95
62
- launchHaskellLanguageServer :: Arguments -> IO ()
96
+ launchHaskellLanguageServer :: Arguments -> IO (Either WrapperSetupError () )
63
97
launchHaskellLanguageServer parsedArgs = do
64
98
case parsedArgs of
65
99
Ghcide GhcideArguments {.. } -> whenJust argsCwd setCurrentDirectory
@@ -75,7 +109,10 @@ launchHaskellLanguageServer parsedArgs = do
75
109
76
110
case parsedArgs of
77
111
Ghcide GhcideArguments {.. } ->
78
- when argsProjectGhcVersion $ getRuntimeGhcVersion' cradle >>= putStrLn >> exitSuccess
112
+ when argsProjectGhcVersion $ do
113
+ runExceptT (getRuntimeGhcVersion' cradle) >>= \ case
114
+ Right ghcVersion -> putStrLn ghcVersion >> exitSuccess
115
+ Left err -> T. putStrLn (prettyError err NoShorten ) >> exitFailure
79
116
_ -> pure ()
80
117
81
118
progName <- getProgName
@@ -94,64 +131,74 @@ launchHaskellLanguageServer parsedArgs = do
94
131
hPutStrLn stderr " "
95
132
-- Get the ghc version -- this might fail!
96
133
hPutStrLn stderr " Consulting the cradle to get project GHC version..."
97
- ghcVersion <- getRuntimeGhcVersion' cradle
98
- hPutStrLn stderr $ " Project GHC version: " ++ ghcVersion
99
134
100
- let
101
- hlsBin = " haskell-language-server-" ++ ghcVersion
102
- candidates' = [hlsBin, " haskell-language-server" ]
103
- candidates = map (++ exeExtension) candidates'
135
+ runExceptT $ do
136
+ ghcVersion <- getRuntimeGhcVersion' cradle
137
+ liftIO $ hPutStrLn stderr $ " Project GHC version: " ++ ghcVersion
104
138
105
- hPutStrLn stderr $ " haskell-language-server exe candidates: " ++ show candidates
139
+ let
140
+ hlsBin = " haskell-language-server-" ++ ghcVersion
141
+ candidates' = [hlsBin, " haskell-language-server" ]
142
+ candidates = map (++ exeExtension) candidates'
106
143
107
- mexes <- traverse findExecutable candidates
144
+ liftIO $ hPutStrLn stderr $ " haskell-language-server exe candidates: " ++ show candidates
145
+
146
+ mexes <- liftIO $ traverse findExecutable candidates
147
+
148
+ case asum mexes of
149
+ Nothing -> throwE (NoLanguageServer ghcVersion candidates)
150
+ Just e -> do
151
+ liftIO $ hPutStrLn stderr $ " Launching haskell-language-server exe at:" ++ e
108
152
109
- case asum mexes of
110
- Nothing -> die $ " Cannot find any haskell-language-server exe, looked for: " ++ intercalate " , " candidates
111
- Just e -> do
112
- hPutStrLn stderr $ " Launching haskell-language-server exe at:" ++ e
113
153
#ifdef mingw32_HOST_OS
114
- callProcess e args
154
+ liftIO $ callProcess e args
115
155
#else
116
- let Cradle { cradleOptsProg = CradleAction { runGhcCmd } } = cradle
117
- -- we need to be compatible with NoImplicitPrelude
118
- ghcBinary <- (fmap trim <$> runGhcCmd [" -v0" , " -package-env=-" , " -ignore-dot-ghci" , " -e" , " Control.Monad.join (Control.Monad.fmap System.IO.putStr System.Environment.getExecutablePath)" ])
119
- >>= cradleResult " Failed to get project GHC executable path"
120
- libdir <- HieBios. getRuntimeGhcLibDir cradle
121
- >>= cradleResult " Failed to get project GHC libdir path"
122
- env <- Map. fromList <$> getEnvironment
123
- let newEnv = Map. insert " GHC_BIN" ghcBinary $ Map. insert " GHC_LIBDIR" libdir env
124
- executeFile e True args (Just (Map. toList newEnv))
156
+
157
+ let Cradle { cradleOptsProg = CradleAction { runGhcCmd } } = cradle
158
+
159
+ let cradleName = actionName (cradleOptsProg cradle)
160
+ -- we need to be compatible with NoImplicitPrelude
161
+ ghcBinary <- liftIO (fmap trim <$> runGhcCmd [" -v0" , " -package-env=-" , " -ignore-dot-ghci" , " -e" , " Control.Monad.join (Control.Monad.fmap System.IO.putStr System.Environment.getExecutablePath)" ])
162
+ >>= cradleResult cradleName
163
+
164
+ libdir <- liftIO (HieBios. getRuntimeGhcLibDir cradle)
165
+ >>= cradleResult cradleName
166
+
167
+ env <- Map. fromList <$> liftIO getEnvironment
168
+ let newEnv = Map. insert " GHC_BIN" ghcBinary $ Map. insert " GHC_LIBDIR" libdir env
169
+ liftIO $ executeFile e True args (Just (Map. toList newEnv))
125
170
#endif
126
171
127
172
128
- cradleResult :: String -> CradleLoadResult a -> IO a
129
- cradleResult _ (CradleSuccess a) = pure a
130
- cradleResult str (CradleFail e) = die $ str ++ " : " ++ show e
131
- cradleResult str CradleNone = die $ str ++ " : no cradle"
173
+
174
+ cradleResult :: ActionName Void -> CradleLoadResult a -> ExceptT WrapperSetupError IO a
175
+ cradleResult _ (CradleSuccess ver) = pure ver
176
+ cradleResult cradleName (CradleFail error ) = throwE $ FailedToObtainGhcVersion cradleName error
177
+ cradleResult cradleName CradleNone = throwE $ NoneCradleGhcVersion cradleName
132
178
133
179
-- | Version of 'getRuntimeGhcVersion' that dies if we can't get it, and also
134
180
-- checks to see if the tool is missing if it is one of
135
- getRuntimeGhcVersion' :: Show a => Cradle a -> IO String
181
+ getRuntimeGhcVersion' :: Cradle Void -> ExceptT WrapperSetupError IO String
136
182
getRuntimeGhcVersion' cradle = do
183
+ let cradleName = actionName (cradleOptsProg cradle)
137
184
138
185
-- See if the tool is installed
139
- case actionName (cradleOptsProg cradle) of
186
+ case cradleName of
140
187
Stack -> checkToolExists " stack"
141
188
Cabal -> checkToolExists " cabal"
142
189
Default -> checkToolExists " ghc"
143
190
Direct -> checkToolExists " ghc"
144
191
_ -> pure ()
145
192
146
- HieBios. getRuntimeGhcVersion cradle >>= cradleResult " Failed to get project GHC version"
193
+ ghcVersionRes <- liftIO $ HieBios. getRuntimeGhcVersion cradle
194
+ cradleResult cradleName ghcVersionRes
195
+
147
196
where
148
197
checkToolExists exe = do
149
- exists <- findExecutable exe
198
+ exists <- liftIO $ findExecutable exe
150
199
case exists of
151
200
Just _ -> pure ()
152
- Nothing ->
153
- die $ " Cradle requires " ++ exe ++ " but couldn't find it" ++ " \n "
154
- ++ show cradle
201
+ Nothing -> throwE $ ToolRequirementMissing exe (actionName (cradleOptsProg cradle))
155
202
156
203
findProjectCradle :: IO (Cradle Void )
157
204
findProjectCradle = findProjectCradle' True
@@ -175,3 +222,93 @@ trim :: String -> String
175
222
trim s = case lines s of
176
223
[] -> s
177
224
ls -> dropWhileEnd isSpace $ last ls
225
+
226
+ data WrapperSetupError
227
+ = FailedToObtainGhcVersion (ActionName Void ) CradleError
228
+ | NoneCradleGhcVersion (ActionName Void )
229
+ | NoLanguageServer String [FilePath ]
230
+ | ToolRequirementMissing String (ActionName Void )
231
+ deriving (Show )
232
+
233
+ data Shorten = Shorten | NoShorten
234
+
235
+ -- | Pretty error message displayable to the future.
236
+ -- Extra argument 'Shorten' can be used to shorten error message.
237
+ -- Reduces usefulness, but allows us to show the error message via LSP
238
+ -- as LSP doesn't allow any newlines and makes it really hard to read
239
+ -- the message otherwise.
240
+ prettyError :: WrapperSetupError -> Shorten -> T. Text
241
+ prettyError (FailedToObtainGhcVersion name crdlError) shorten =
242
+ " Failed to find the GHC version of this " <> T. pack (show name) <> " project." <>
243
+ case shorten of
244
+ Shorten ->
245
+ " \n " <> T. pack (fromMaybe " " . listToMaybe $ cradleErrorStderr crdlError)
246
+ NoShorten ->
247
+ " \n " <> T. pack (intercalate " \n " (cradleErrorStderr crdlError))
248
+ prettyError (NoneCradleGhcVersion name) _ =
249
+ " Failed to get the GHC version of this " <> T. pack (show name) <>
250
+ " project because a none cradle is configured"
251
+ prettyError (NoLanguageServer ghcVersion candidates) _ =
252
+ " Failed to find a HLS version for GHC " <> T. pack ghcVersion <>
253
+ " \n Executable names we failed to find: " <> T. pack (intercalate " ," candidates)
254
+ prettyError (ToolRequirementMissing toolExe name) _ =
255
+ " Failed to find executable \" " <> T. pack toolExe <> " \" in $PATH for this " <> T. pack (show name) <> " project."
256
+
257
+ newtype ErrorLSPM c a = ErrorLSPM { unErrorLSPM :: (LspM c ) a }
258
+ deriving (Functor , Applicative , Monad , MonadIO , MonadUnliftIO , LSP.MonadLsp c)
259
+
260
+ -- | Launches a LSP that displays an error and presents the user with a request
261
+ -- to shut down the LSP.
262
+ launchErrorLSP :: T. Text -> IO ()
263
+ launchErrorLSP errorMsg = do
264
+ recorder <- makeDefaultStderrRecorder Nothing Info
265
+
266
+ let logger = Logger $ \ p m -> logger_ recorder (WithPriority p emptyCallStack (pretty m))
267
+
268
+ let defaultArguments = Main. defaultArguments (cmapWithPrio pretty recorder) logger
269
+
270
+ inH <- Main. argsHandleIn defaultArguments
271
+
272
+ outH <- Main. argsHandleOut defaultArguments
273
+
274
+ let onConfigurationChange cfg _ = Right cfg
275
+
276
+ let setup clientMsgVar = do
277
+ -- Forcefully exit
278
+ let exit = void $ tryPutMVar clientMsgVar ()
279
+
280
+ let doInitialize :: LSP. LanguageContextEnv Config -> RequestMessage Initialize -> IO (Either ResponseError (LSP. LanguageContextEnv Config , () ))
281
+ doInitialize env _ = do
282
+
283
+ let restartTitle = " Try to restart"
284
+ void $ LSP. runLspT env $ LSP. sendRequest SWindowShowMessageRequest (ShowMessageRequestParams MtError errorMsg (Just [MessageActionItem restartTitle])) $ \ case
285
+ Right (Just (MessageActionItem title))
286
+ | title == restartTitle -> liftIO exit
287
+ _ -> pure ()
288
+
289
+ pure (Right (env, () ))
290
+
291
+ let asyncHandlers = mconcat
292
+ [ exitHandler exit ]
293
+
294
+ let interpretHandler (env, _st) = LSP. Iso (LSP. runLspT env . unErrorLSPM) liftIO
295
+ pure (doInitialize, asyncHandlers, interpretHandler)
296
+
297
+ runLanguageServer
298
+ (Main. argsLspOptions defaultArguments)
299
+ inH
300
+ outH
301
+ (Main. argsDefaultHlsConfig defaultArguments)
302
+ onConfigurationChange
303
+ setup
304
+
305
+ exitHandler :: IO () -> LSP. Handlers (ErrorLSPM c )
306
+ exitHandler exit = LSP. notificationHandler SExit $ const $ liftIO exit
307
+
308
+ hlsWrapperLogger :: Logger
309
+ hlsWrapperLogger = Logger $ \ pri txt ->
310
+ case pri of
311
+ Debug -> debugm (T. unpack txt)
312
+ Info -> logm (T. unpack txt)
313
+ Warning -> warningm (T. unpack txt)
314
+ Error -> errorm (T. unpack txt)
0 commit comments