Skip to content

Commit 2280b6d

Browse files
committed
Turn HLS-wrapper into a LSP Server
Turn HLS-wrapper into a full-blown LSP server, capable of sending requests and handling them appropriately. Introduces better error handling to HLS-wrapper to show LSP clients dedicated error messages. This should help users understand why their Language Server isn't starting.
1 parent 5714207 commit 2280b6d

File tree

3 files changed

+349
-36
lines changed

3 files changed

+349
-36
lines changed

exe/Wrapper.hs

Lines changed: 88 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -1,15 +1,22 @@
1-
{-# LANGUAGE RecordWildCards #-}
1+
{-# LANGUAGE LambdaCase #-}
2+
{-# LANGUAGE OverloadedStrings #-}
3+
{-# LANGUAGE RecordWildCards #-}
24
-- | This module is based on the hie-wrapper.sh script in
35
-- https://github.com/alanz/vscode-hie-server
46
module Main where
57

68
import Control.Monad.Extra
9+
import Control.Monad.IO.Class
10+
import Control.Monad.Trans.Except
711
import Data.Default
812
import Data.Foldable
913
import Data.List
14+
import Data.Maybe
15+
import qualified Data.Text as T
16+
import qualified Data.Text.IO as T
1017
import Data.Void
11-
import qualified Development.IDE.Session as Session
12-
import qualified HIE.Bios.Environment as HieBios
18+
import qualified Development.IDE.Session as Session
19+
import qualified HIE.Bios.Environment as HieBios
1320
import HIE.Bios.Types
1421
import Ide.Arguments
1522
import Ide.Version
@@ -20,6 +27,7 @@ import System.FilePath
2027
import System.IO
2128
import System.Info
2229
import System.Process
30+
import WrapperLspMain
2331

2432
-- ---------------------------------------------------------------------
2533

@@ -46,9 +54,17 @@ main = do
4654
BiosMode PrintCradleType ->
4755
print =<< findProjectCradle
4856

49-
_ -> launchHaskellLanguageServer args
57+
_ -> launchHaskellLanguageServer args >>= \case
58+
Right () -> pure ()
59+
Left err -> do
60+
T.hPutStrLn stderr "*** Startup ERROR"
61+
T.hPutStrLn stderr (prettyError err NoShorten)
62+
case args of
63+
Ghcide ghcideArguments -> lspMain ghcideArguments (prettyError err Shorten)
64+
_ -> pure ()
5065

51-
launchHaskellLanguageServer :: Arguments -> IO ()
66+
67+
launchHaskellLanguageServer :: Arguments -> IO (Either WrapperSetupError ())
5268
launchHaskellLanguageServer parsedArgs = do
5369
case parsedArgs of
5470
Ghcide GhcideArguments{..} -> whenJust argsCwd setCurrentDirectory
@@ -64,7 +80,10 @@ launchHaskellLanguageServer parsedArgs = do
6480

6581
case parsedArgs of
6682
Ghcide GhcideArguments{..} ->
67-
when argsProjectGhcVersion $ getRuntimeGhcVersion' cradle >>= putStrLn >> exitSuccess
83+
when argsProjectGhcVersion $ do
84+
runExceptT (getRuntimeGhcVersion' cradle) >>= \case
85+
Right ghcVersion -> putStrLn ghcVersion >> exitSuccess
86+
Left err -> T.putStrLn (prettyError err NoShorten) >> exitFailure
6887
_ -> pure ()
6988

7089
progName <- getProgName
@@ -83,51 +102,53 @@ launchHaskellLanguageServer parsedArgs = do
83102
hPutStrLn stderr ""
84103
-- Get the ghc version -- this might fail!
85104
hPutStrLn stderr "Consulting the cradle to get project GHC version..."
86-
ghcVersion <- getRuntimeGhcVersion' cradle
87-
hPutStrLn stderr $ "Project GHC version: " ++ ghcVersion
88-
89-
let
90-
hlsBin = "haskell-language-server-" ++ ghcVersion
91-
candidates' = [hlsBin, "haskell-language-server"]
92-
candidates = map (++ exeExtension) candidates'
93-
94-
hPutStrLn stderr $ "haskell-language-server exe candidates: " ++ show candidates
95-
96-
mexes <- traverse findExecutable candidates
97-
98-
case asum mexes of
99-
Nothing -> hPutStrLn stderr $ "Cannot find any haskell-language-server exe, looked for: " ++ intercalate ", " candidates
100-
Just e -> do
101-
hPutStrLn stderr $ "Launching haskell-language-server exe at:" ++ e
102-
callProcess e args
103-
104-
-- | Version of 'getRuntimeGhcVersion' that dies if we can't get it, and also
105-
-- checks to see if the tool is missing if it is one of
106-
getRuntimeGhcVersion' :: Show a => Cradle a -> IO String
105+
runExceptT (getRuntimeGhcVersion' cradle) >>= \case
106+
Left err -> pure $ Left err
107+
Right ghcVersion -> do
108+
hPutStrLn stderr $ "Project GHC version: " ++ ghcVersion
109+
110+
let
111+
hlsBin = "haskell-language-server-" ++ ghcVersion
112+
candidates' = [hlsBin, "haskell-language-server"]
113+
candidates = map (++ exeExtension) candidates'
114+
115+
hPutStrLn stderr $ "haskell-language-server exe candidates: " ++ show candidates
116+
117+
mexes <- traverse findExecutable candidates
118+
119+
case asum mexes of
120+
Nothing -> pure $ Left $ NoLanguageServer ghcVersion candidates
121+
Just e -> do
122+
hPutStrLn stderr $ "Launching haskell-language-server exe at:" ++ e
123+
callProcess e args
124+
pure $ Right ()
125+
126+
-- | Version of 'getRuntimeGhcVersion' that throws a 'WrapperSetupError' if we
127+
-- can't get it, and also checks if run-time tool dependencies are missing.
128+
getRuntimeGhcVersion' :: Cradle Void -> ExceptT WrapperSetupError IO String
107129
getRuntimeGhcVersion' cradle = do
108130

131+
let cradleName = actionName (cradleOptsProg cradle)
109132
-- See if the tool is installed
110-
case actionName (cradleOptsProg cradle) of
133+
case cradleName of
111134
Stack -> checkToolExists "stack"
112135
Cabal -> checkToolExists "cabal"
113136
Default -> checkToolExists "ghc"
114137
Direct -> checkToolExists "ghc"
115138
_ -> pure ()
116139

117-
ghcVersionRes <- HieBios.getRuntimeGhcVersion cradle
140+
ghcVersionRes <- liftIO $ HieBios.getRuntimeGhcVersion cradle
118141
case ghcVersionRes of
119142
CradleSuccess ver -> do
120143
return ver
121-
CradleFail error -> die $ "Failed to get project GHC version:" ++ show error
122-
CradleNone -> die "Failed get project GHC version, since we have a none cradle"
144+
CradleFail error -> throwE $ FailedToObtainGhcVersion cradleName error
145+
CradleNone -> throwE $ NoneCradleGhcVersion cradleName
123146
where
124147
checkToolExists exe = do
125-
exists <- findExecutable exe
148+
exists <- liftIO $ findExecutable exe
126149
case exists of
127150
Just _ -> pure ()
128-
Nothing ->
129-
die $ "Cradle requires " ++ exe ++ " but couldn't find it" ++ "\n"
130-
++ show cradle
151+
Nothing -> throwE $ ToolRequirementMissing exe (actionName (cradleOptsProg cradle))
131152

132153
findProjectCradle :: IO (Cradle Void)
133154
findProjectCradle = do
@@ -142,3 +163,35 @@ findProjectCradle = do
142163
Nothing -> hPutStrLn stderr "No 'hie.yaml' found. Try to discover the project type!"
143164

144165
Session.loadCradle def hieYaml d
166+
167+
data WrapperSetupError
168+
= FailedToObtainGhcVersion (ActionName Void) CradleError
169+
| NoneCradleGhcVersion (ActionName Void)
170+
| NoLanguageServer String [FilePath]
171+
| ToolRequirementMissing String (ActionName Void)
172+
deriving (Show)
173+
174+
data Shorten = Shorten | NoShorten
175+
176+
-- | Pretty error message displayable to the future.
177+
-- Extra argument 'Shorten' can be used to shorten error message.
178+
-- Reduces usefulness, but allows us to show the error message via LSP
179+
-- as LSP doesn't allow any newlines and makes it really hard to read
180+
-- the message otherwise.
181+
prettyError :: WrapperSetupError -> Shorten -> T.Text
182+
prettyError (FailedToObtainGhcVersion name crdlError) shorten =
183+
"Failed to find the GHC version of this " <> T.pack (show name) <> " project." <>
184+
case shorten of
185+
Shorten ->
186+
"\n" <> T.pack (fromMaybe "" . listToMaybe $ cradleErrorStderr crdlError)
187+
NoShorten ->
188+
"\n" <> T.pack (intercalate "\n" (cradleErrorStderr crdlError))
189+
prettyError (NoneCradleGhcVersion name) _ =
190+
"Failed to get the GHC version of the " <> T.pack (show name) <>
191+
" project, since we have a none cradle"
192+
prettyError (NoLanguageServer ghcVersion candidates) _ =
193+
"Failed to find a HLS version for GHC " <> T.pack ghcVersion <>
194+
"\nExecutable names we failed to find: " <> T.pack (intercalate "," candidates)
195+
prettyError (ToolRequirementMissing toolExe name) _ =
196+
"This is a " <> T.pack (show name) <> " Project, but we failed to find \"" <>
197+
T.pack toolExe <> "\" on the $PATH"

0 commit comments

Comments
 (0)