4
4
{-# LANGUAGE TypeFamilies #-}
5
5
{-# LANGUAGE MultiParamTypeClasses #-}
6
6
{-# LANGUAGE FlexibleInstances #-}
7
- {-# LANGUAGE LambdaCase #-}
8
7
{-# LANGUAGE TupleSections #-}
9
8
{-# LANGUAGE OverloadedStrings #-}
10
9
@@ -24,6 +23,7 @@ module Haskell.Ide.Engine.ModuleCache
24
23
, cacheInfoNoClear
25
24
, runActionWithContext
26
25
, ModuleCache (.. )
26
+ , PublishDiagnostics
27
27
) where
28
28
29
29
@@ -32,26 +32,28 @@ import Control.Monad
32
32
import Control.Monad.IO.Class
33
33
import Control.Monad.Trans.Control
34
34
import Control.Monad.Trans.Free
35
+ import qualified Data.Aeson as Aeson
36
+ import qualified Data.ByteString.Char8 as B
35
37
import Data.Dynamic (toDyn , fromDynamic , Dynamic )
36
38
import Data.Generics (Proxy (.. ), TypeRep , typeRep , typeOf )
37
39
import qualified Data.Map as Map
38
40
import Data.Maybe
41
+ import qualified Data.SortedList as SL
42
+ import qualified Data.Trie.Convenience as T
43
+ import qualified Data.Trie as T
44
+ import qualified Data.Text as Text
39
45
import Data.Typeable (Typeable )
46
+ import qualified Data.Yaml as Yaml
40
47
import System.Directory
41
48
42
49
43
50
import qualified GHC
44
51
import qualified HscMain as GHC
52
+ import qualified HIE.Bios as Bios
53
+ import qualified HIE.Bios.Ghc.Api as Bios
45
54
46
- import qualified Data.Aeson as Aeson
47
- import qualified Data.Trie.Convenience as T
48
- import qualified Data.Trie as T
49
- import qualified Data.Text as Text
50
- import qualified Data.Yaml as Yaml
51
- import qualified HIE.Bios as BIOS
52
- import qualified HIE.Bios.Ghc.Api as BIOS
53
- import qualified Data.ByteString.Char8 as B
54
-
55
+ import qualified Language.Haskell.LSP.Types as J
56
+ import qualified Language.Haskell.LSP.Diagnostics as J
55
57
import Haskell.Ide.Engine.ArtifactMap
56
58
import Haskell.Ide.Engine.Cradle (findLocalCradle , cradleDisplay )
57
59
import Haskell.Ide.Engine.TypeMap
@@ -68,6 +70,9 @@ modifyCache :: (HasGhcModuleCache m) => (GhcModuleCache -> GhcModuleCache) -> m
68
70
modifyCache f = modifyModuleCache f
69
71
70
72
-- ---------------------------------------------------------------------
73
+
74
+ type PublishDiagnostics = Int -> J. NormalizedUri -> J. TextDocumentVersion -> J. DiagnosticsBySource -> IO ()
75
+
71
76
-- | Run the given action in context and initialise a session with hie-bios.
72
77
-- If a context is given, the context is used to initialise a session for GHC.
73
78
-- The project "hie-bios" is used to find a Cradle and setup a GHC session
@@ -88,22 +93,23 @@ modifyCache f = modifyModuleCache f
88
93
-- though we know nothing about the file.
89
94
-- 2. Return the default value for the specific action.
90
95
runActionWithContext :: (MonadIde m , GHC. GhcMonad m , HasGhcModuleCache m , MonadBaseControl IO m )
91
- => GHC. DynFlags
96
+ => PublishDiagnostics
97
+ -> GHC. DynFlags
92
98
-> Maybe FilePath -- ^ Context for the Action
93
99
-> a -- ^ Default value for none cradle
94
100
-> m a -- ^ Action to execute
95
101
-> m (IdeResult a ) -- ^ Result of the action or error in
96
102
-- the context initialisation.
97
- runActionWithContext _df Nothing _def action =
103
+ runActionWithContext _pub _df Nothing _def action =
98
104
-- Cradle with no additional flags
99
105
-- dir <- liftIO $ getCurrentDirectory
100
106
-- This causes problems when loading a later package which sets the
101
107
-- packageDb
102
- -- loadCradle df (BIOS .defaultCradle dir)
108
+ -- loadCradle df (Bios .defaultCradle dir)
103
109
fmap IdeResultOk action
104
- runActionWithContext df (Just uri) def action = do
110
+ runActionWithContext publishDiagnostics df (Just uri) def action = do
105
111
mcradle <- getCradle uri
106
- loadCradle df mcradle def action
112
+ loadCradle publishDiagnostics df mcradle def action
107
113
108
114
-- ---------------------------------------------------------------------
109
115
@@ -114,17 +120,18 @@ runActionWithContext df (Just uri) def action = do
114
120
-- to set up the Session, including downloading all dependencies of a Cradle.
115
121
loadCradle :: forall a m . (MonadIde m , HasGhcModuleCache m , GHC. GhcMonad m
116
122
, MonadBaseControl IO m )
117
- => GHC. DynFlags
123
+ => PublishDiagnostics
124
+ -> GHC. DynFlags
118
125
-> LookupCradleResult
119
126
-> a
120
127
-> m a
121
128
-> m (IdeResult a )
122
- loadCradle _ ReuseCradle _def action = do
129
+ loadCradle _ _ ReuseCradle _def action = do
123
130
-- Since we expect this message to show up often, only show in debug mode
124
131
debugm " Reusing cradle"
125
132
IdeResultOk <$> action
126
133
127
- loadCradle _iniDynFlags (LoadCradle (CachedCradle crd env)) _def action = do
134
+ loadCradle _ _iniDynFlags (LoadCradle (CachedCradle crd env)) _def action = do
128
135
-- Reloading a cradle happens on component switch
129
136
logm $ " Switch to cradle: " ++ show crd
130
137
-- Cache the existing cradle
@@ -133,7 +140,7 @@ loadCradle _iniDynFlags (LoadCradle (CachedCradle crd env)) _def action = do
133
140
setCurrentCradle crd
134
141
IdeResultOk <$> action
135
142
136
- loadCradle iniDynFlags (NewCradle fp) def action = do
143
+ loadCradle publishDiagnostics iniDynFlags (NewCradle fp) def action = do
137
144
-- If this message shows up a lot in the logs, it is an indicator for a bug
138
145
logm $ " New cradle: " ++ fp
139
146
-- Cache the existing cradle
@@ -156,34 +163,49 @@ loadCradle iniDynFlags (NewCradle fp) def action = do
156
163
where
157
164
-- | Initialise the given cradle. This might fail and return an error via `IdeResultFail`.
158
165
-- Reports its progress to the client.
159
- initialiseCradle :: (MonadIde m , HasGhcModuleCache m , GHC. GhcMonad m , MonadBaseControl IO m )
160
- => BIOS . Cradle -> (Progress -> IO () ) -> m (IdeResult a )
166
+ initialiseCradle :: (MonadIde m , HasGhcModuleCache m , GHC. GhcMonad m )
167
+ => Bios . Cradle -> (Progress -> IO () ) -> m (IdeResult a )
161
168
initialiseCradle cradle f = do
162
- res <- BIOS . initializeFlagsWithCradleWithMessage (Just (toMessager f)) fp cradle
169
+ res <- Bios . initializeFlagsWithCradleWithMessage (Just (toMessager f)) fp cradle
163
170
case res of
164
- BIOS . CradleNone ->
171
+ Bios . CradleNone ->
165
172
-- Note: The action is not run if we are in the none cradle, we
166
173
-- just pretend the file doesn't exist.
167
174
return $ IdeResultOk def
168
- BIOS. CradleFail err -> do
169
- logm $ " Fail on cradle initialisation: " ++ show err
175
+ Bios. CradleFail (Bios. CradleError code msg) -> do
176
+ warningm $ " Fail on cradle initialisation: (" ++ show code ++ " )" ++ show msg
177
+
178
+ -- Send a detailed diagnostic to the user.
179
+
180
+ let normalizedUri = J. toNormalizedUri (filePathToUri fp)
181
+ sev = Just DsError
182
+ range = Range (Position 0 0 ) (Position 1 0 )
183
+ msgTxt =
184
+ [ " Fail on initialisation for \" " <> Text. pack fp <> " \" ."
185
+ ] <> map Text. pack msg
186
+ source = Just " bios"
187
+ diag = Diagnostic range sev Nothing source (Text. unlines msgTxt) Nothing
188
+
189
+ liftIO $ publishDiagnostics maxBound normalizedUri Nothing
190
+ (Map. singleton source (SL. singleton diag))
191
+
170
192
return $ IdeResultFail $ IdeError
171
193
{ ideCode = OtherError
172
- , ideMessage = Text. pack $ show err
194
+ , ideMessage = Text. unwords ( take 2 msgTxt)
173
195
, ideInfo = Aeson. Null
174
196
}
175
- BIOS . CradleSuccess init_session -> do
197
+ Bios . CradleSuccess init_session -> do
176
198
-- Note that init_session contains a Hook to 'f'.
177
199
-- So, it can still provide Progress Reports.
178
200
-- Therefore, invocation of 'init_session' must happen
179
201
-- while 'f' is still valid.
180
202
liftIO (GHC. newHscEnv iniDynFlags) >>= GHC. setSession
181
- liftIO $ setCurrentDirectory (BIOS . cradleRootDir cradle)
203
+ liftIO $ setCurrentDirectory (Bios . cradleRootDir cradle)
182
204
183
205
let onGhcError = return . Left
184
206
let onSourceError srcErr = do
185
207
logm $ " Source error on cradle initialisation: " ++ show srcErr
186
- return $ Right BIOS . Failed
208
+ return $ Right Bios . Failed
187
209
-- We continue setting the cradle in case the file has source errors
188
210
-- cause they will be reported to user by diagnostics
189
211
init_res <- gcatches
@@ -202,12 +224,12 @@ loadCradle iniDynFlags (NewCradle fp) def action = do
202
224
-- it on a save whilst there are errors. Subsequent loads won't
203
225
-- be that slow, even though the cradle isn't cached because the
204
226
-- `.hi` files will be saved.
205
- Right BIOS . Succeeded -> do
227
+ Right Bios . Succeeded -> do
206
228
setCurrentCradle cradle
207
229
logm " Cradle set succesfully"
208
230
IdeResultOk <$> action
209
231
210
- Right BIOS . Failed -> do
232
+ Right Bios . Failed -> do
211
233
setCurrentCradle cradle
212
234
logm " Cradle did not load succesfully"
213
235
IdeResultOk <$> action
@@ -217,7 +239,7 @@ loadCradle iniDynFlags (NewCradle fp) def action = do
217
239
-- that belong to this cradle.
218
240
-- If the cradle does not load any module, it is responsible for an empty
219
241
-- list of Modules.
220
- setCurrentCradle :: (HasGhcModuleCache m , GHC. GhcMonad m ) => BIOS . Cradle -> m ()
242
+ setCurrentCradle :: (HasGhcModuleCache m , GHC. GhcMonad m ) => Bios . Cradle -> m ()
221
243
setCurrentCradle cradle = do
222
244
mg <- GHC. getModuleGraph
223
245
let ps = mapMaybe (GHC. ml_hs_file . GHC. ms_location) (mgModSummaries mg)
@@ -230,7 +252,7 @@ setCurrentCradle cradle = do
230
252
-- for.
231
253
-- Via 'lookupCradle' it can be checked if a given FilePath is managed by
232
254
-- a any Cradle that has already been loaded.
233
- cacheCradle :: (HasGhcModuleCache m , GHC. GhcMonad m ) => ([FilePath ], BIOS . Cradle ) -> m ()
255
+ cacheCradle :: (HasGhcModuleCache m , GHC. GhcMonad m ) => ([FilePath ], Bios . Cradle ) -> m ()
234
256
cacheCradle (ds, c) = do
235
257
env <- GHC. getSession
236
258
let cc = CachedCradle c env
0 commit comments