1
- {-# LANGUAGE RecordWildCards #-}
1
+ {-# LANGUAGE LambdaCase #-}
2
+ {-# LANGUAGE OverloadedStrings #-}
3
+ {-# LANGUAGE RecordWildCards #-}
2
4
-- | This module is based on the hie-wrapper.sh script in
3
5
-- https://github.com/alanz/vscode-hie-server
4
6
module Main where
5
7
6
8
import Control.Monad.Extra
9
+ import Control.Monad.IO.Class
10
+ import Control.Monad.Trans.Except
7
11
import Data.Default
8
12
import Data.Foldable
9
13
import Data.List
14
+ import Data.Maybe
15
+ import qualified Data.Text as T
16
+ import qualified Data.Text.IO as T
10
17
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
13
20
import HIE.Bios.Types
14
21
import Ide.Arguments
15
22
import Ide.Version
@@ -20,6 +27,7 @@ import System.FilePath
20
27
import System.IO
21
28
import System.Info
22
29
import System.Process
30
+ import WrapperLspMain
23
31
24
32
-- ---------------------------------------------------------------------
25
33
@@ -46,9 +54,17 @@ main = do
46
54
BiosMode PrintCradleType ->
47
55
print =<< findProjectCradle
48
56
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 ()
50
65
51
- launchHaskellLanguageServer :: Arguments -> IO ()
66
+
67
+ launchHaskellLanguageServer :: Arguments -> IO (Either WrapperSetupError () )
52
68
launchHaskellLanguageServer parsedArgs = do
53
69
case parsedArgs of
54
70
Ghcide GhcideArguments {.. } -> whenJust argsCwd setCurrentDirectory
@@ -64,7 +80,10 @@ launchHaskellLanguageServer parsedArgs = do
64
80
65
81
case parsedArgs of
66
82
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
68
87
_ -> pure ()
69
88
70
89
progName <- getProgName
@@ -83,51 +102,53 @@ launchHaskellLanguageServer parsedArgs = do
83
102
hPutStrLn stderr " "
84
103
-- Get the ghc version -- this might fail!
85
104
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
107
129
getRuntimeGhcVersion' cradle = do
108
130
131
+ let cradleName = actionName (cradleOptsProg cradle)
109
132
-- See if the tool is installed
110
- case actionName (cradleOptsProg cradle) of
133
+ case cradleName of
111
134
Stack -> checkToolExists " stack"
112
135
Cabal -> checkToolExists " cabal"
113
136
Default -> checkToolExists " ghc"
114
137
Direct -> checkToolExists " ghc"
115
138
_ -> pure ()
116
139
117
- ghcVersionRes <- HieBios. getRuntimeGhcVersion cradle
140
+ ghcVersionRes <- liftIO $ HieBios. getRuntimeGhcVersion cradle
118
141
case ghcVersionRes of
119
142
CradleSuccess ver -> do
120
143
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
123
146
where
124
147
checkToolExists exe = do
125
- exists <- findExecutable exe
148
+ exists <- liftIO $ findExecutable exe
126
149
case exists of
127
150
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))
131
152
132
153
findProjectCradle :: IO (Cradle Void )
133
154
findProjectCradle = do
@@ -142,3 +163,35 @@ findProjectCradle = do
142
163
Nothing -> hPutStrLn stderr " No 'hie.yaml' found. Try to discover the project type!"
143
164
144
165
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
+ " \n Executable 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