22
22
module Ide.Plugin.Eval where
23
23
24
24
import Control.Monad (void )
25
- import Control.Monad.Catch (MonadMask , bracket )
26
25
import Control.Monad.IO.Class (MonadIO (liftIO ))
27
26
import Control.Monad.Trans.Class (MonadTrans (lift ))
28
27
import Control.Monad.Trans.Except (ExceptT (.. ), runExceptT ,
@@ -45,8 +44,7 @@ import Development.IDE.Types.Location (toNormalizedFilePath',
45
44
uriToFilePath' )
46
45
import DynamicLoading (initializePlugins )
47
46
import DynFlags (targetPlatform )
48
- import GHC (DynFlags , ExecResult (.. ),
49
- GeneralFlag (Opt_IgnoreHpcChanges , Opt_IgnoreOptimChanges , Opt_ImplicitImportQualified ),
47
+ import GHC (DynFlags , ExecResult (.. ), GeneralFlag (Opt_IgnoreHpcChanges , Opt_IgnoreOptimChanges , Opt_ImplicitImportQualified ),
50
48
GhcLink (LinkInMemory ),
51
49
GhcMode (CompManager ),
52
50
HscTarget (HscInterpreted ),
@@ -80,9 +78,9 @@ import Language.Haskell.LSP.Core (LspFuncs (getVirtualFileFunc))
80
78
import Language.Haskell.LSP.Types
81
79
import Language.Haskell.LSP.VFS (virtualFileText )
82
80
import PrelNames (pRELUDE )
83
- import System.IO ( Handle , IOMode ( WriteMode ),
84
- hClose , openFile )
85
- import System.IO.Extra ( newTempFile )
81
+ import System.FilePath
82
+ import System.IO ( hClose )
83
+ import System.IO.Temp
86
84
87
85
descriptor :: PluginId -> PluginDescriptor
88
86
descriptor plId =
@@ -97,10 +95,10 @@ extractMatches = goSearch 0 . maybe [] T.lines
97
95
where
98
96
checkMatch = T. stripPrefix " -- >>> "
99
97
looksLikeSplice l
100
- | Just l' <- T. stripPrefix " --" l
101
- = not (" >>>" `T.isPrefixOf` l')
102
- | otherwise
103
- = False
98
+ | Just l' <- T. stripPrefix " --" l =
99
+ not (" >>>" `T.isPrefixOf` l')
100
+ | otherwise =
101
+ False
104
102
105
103
goSearch _ [] = []
106
104
goSearch line (l : ll)
@@ -109,17 +107,17 @@ extractMatches = goSearch 0 . maybe [] T.lines
109
107
| otherwise =
110
108
goSearch (line + 1 ) ll
111
109
112
- goAcc line acc [] = [(reverse acc,Range p p)] where p = Position line 0
113
- goAcc line acc (l: ll)
110
+ goAcc line acc [] = [(reverse acc, Range p p)] where p = Position line 0
111
+ goAcc line acc (l : ll)
114
112
| Just match <- checkMatch l =
115
113
goAcc (line + 1 ) ([(match, line)] <> acc) ll
116
114
| otherwise =
117
- (reverse acc,r) : goSearch (line + 1 ) ll
115
+ (reverse acc, r) : goSearch (line + 1 ) ll
118
116
where
119
117
r = Range p p'
120
118
p = Position line 0
121
119
p' = Position (line + spliceLength) 0
122
- spliceLength = length (takeWhile looksLikeSplice (l: ll))
120
+ spliceLength = length (takeWhile looksLikeSplice (l : ll))
123
121
124
122
provider :: CodeLensProvider
125
123
provider lsp _state plId CodeLensParams {_textDocument} = response $ do
@@ -134,20 +132,21 @@ provider lsp _state plId CodeLensParams {_textDocument} = response $ do
134
132
[ CodeLens range (Just cmd') Nothing
135
133
| (m, r) <- matches,
136
134
let (_, startLine) = head m
137
- (_ , endLine) = last m
135
+ (endLineContents , endLine) = last m
138
136
range = Range start end
139
137
start = Position startLine 0
140
- end = Position endLine 1000
138
+ end = Position endLine ( T. length endLineContents)
141
139
args = EvalParams m r _textDocument,
142
- let cmd' = (cmd :: Command )
143
- {_arguments = Just (List [toJSON args])
144
- ,_title = if trivial r then " Evaluate..." else " Refresh..."
140
+ let cmd' =
141
+ (cmd :: Command )
142
+ { _arguments = Just (List [toJSON args]),
143
+ _title = if trivial r then " Evaluate..." else " Refresh..."
145
144
}
146
145
]
147
146
148
147
return $ List lenses
149
148
where
150
- trivial (Range p p') = p == p'
149
+ trivial (Range p p') = p == p'
151
150
152
151
evalCommandName :: CommandId
153
152
evalCommandName = " evalCommand"
@@ -171,93 +170,98 @@ runEvalCmd lsp state EvalParams {..} = response' $ do
171
170
text <- handleMaybe " contents" $ virtualFileText <$> contents
172
171
173
172
session <-
174
- liftIO
175
- $ runAction " runEvalCmd.ghcSession" state
176
- $ use_ GhcSessionDeps
177
- $ toNormalizedFilePath'
178
- $ fp
173
+ liftIO $
174
+ runAction " runEvalCmd.ghcSession" state $
175
+ use_ GhcSessionDeps $
176
+ toNormalizedFilePath' $
177
+ fp
179
178
180
179
ms <-
181
- liftIO
182
- $ runAction " runEvalCmd.getModSummary" state
183
- $ use_ GetModSummary
184
- $ toNormalizedFilePath'
185
- $ fp
180
+ liftIO $
181
+ runAction " runEvalCmd.getModSummary" state $
182
+ use_ GetModSummary $
183
+ toNormalizedFilePath' $
184
+ fp
186
185
187
186
now <- liftIO getCurrentTime
188
187
189
- withTempFile $ \ temp -> withTempFile $ \ tempLog -> withFile tempLog WriteMode $ \ hLog -> do
188
+ let tmp = withSystemTempFile (takeFileName fp)
189
+
190
+ tmp $ \ temp _h -> tmp $ \ tempLog hLog -> do
191
+ liftIO $ hClose _h
190
192
let modName = moduleName $ ms_mod ms
191
193
thisModuleTarget = Target (TargetFile fp Nothing ) False (Just (textToStringBuffer text, now))
192
194
193
- hscEnv' <- ExceptT $ evalGhcEnv (hscEnv session) $ do
194
- df <- getSessionDynFlags
195
- env <- getSession
196
- df <- liftIO $ setupDynFlagsForGHCiLike env df
197
- _lp <- setSessionDynFlags df
198
-
199
- -- copy the package state to the interactive DynFlags
200
- idflags <- getInteractiveDynFlags
201
- df <- getSessionDynFlags
202
- setInteractiveDynFlags
203
- idflags
204
- { pkgState = pkgState df,
205
- pkgDatabase = pkgDatabase df,
206
- packageFlags = packageFlags df
207
- }
208
-
209
- -- set up a custom log action
210
- setLogAction $ \ _df _wr _sev _span _style _doc ->
211
- defaultLogActionHPutStrDoc _df hLog _doc _style
212
-
213
- -- load the module in the interactive environment
214
- setTargets [thisModuleTarget]
215
- loadResult <- load LoadAllTargets
216
- case loadResult of
217
- Failed -> liftIO $ do
195
+ hscEnv' <- ExceptT $
196
+ evalGhcEnv (hscEnv session) $ do
197
+ df <- getSessionDynFlags
198
+ env <- getSession
199
+ df <- liftIO $ setupDynFlagsForGHCiLike env df
200
+ _lp <- setSessionDynFlags df
201
+
202
+ -- copy the package state to the interactive DynFlags
203
+ idflags <- getInteractiveDynFlags
204
+ df <- getSessionDynFlags
205
+ setInteractiveDynFlags
206
+ idflags
207
+ { pkgState = pkgState df,
208
+ pkgDatabase = pkgDatabase df,
209
+ packageFlags = packageFlags df
210
+ }
211
+
212
+ -- set up a custom log action
213
+ setLogAction $ \ _df _wr _sev _span _style _doc ->
214
+ defaultLogActionHPutStrDoc _df hLog _doc _style
215
+
216
+ -- load the module in the interactive environment
217
+ setTargets [thisModuleTarget]
218
+ loadResult <- load LoadAllTargets
219
+ case loadResult of
220
+ Failed -> liftIO $ do
218
221
hClose hLog
219
222
Left <$> readFile tempLog
220
- Succeeded -> do
223
+ Succeeded -> do
221
224
setContext [IIDecl (simpleImportDecl $ moduleName pRELUDE), IIModule modName]
222
225
Right <$> getSession
223
226
224
227
df <- liftIO $ evalGhcEnv hscEnv' getSessionDynFlags
225
228
let eval (stmt, l)
226
229
| isStmt df stmt = do
227
-
228
230
-- set up a custom interactive print function
229
231
ctxt <- getContext
230
232
setContext [IIDecl (simpleImportDecl $ moduleName pRELUDE)]
231
233
let printFun = " let ghcideCustomShow x = Prelude.writeFile " <> show temp <> " (Prelude.show x)"
232
- interactivePrint <- execStmt printFun execOptions >>= \ case
234
+ interactivePrint <-
235
+ execStmt printFun execOptions >>= \ case
233
236
ExecComplete (Right [interactivePrint]) _ -> pure interactivePrint
234
237
_ -> error " internal error binding print function"
235
238
modifySession $ \ hsc -> hsc {hsc_IC = setInteractivePrintName (hsc_IC hsc) interactivePrint}
236
239
setContext ctxt
237
240
238
241
let opts =
239
- execOptions
242
+ execOptions
240
243
{ execSourceFile = fp,
241
- execLineNumber = l
244
+ execLineNumber = l
242
245
}
243
246
res <- execStmt stmt opts
244
247
str <- case res of
245
- ExecComplete (Left err) _ -> pure $ pad $ show err
246
- ExecComplete (Right _) _ -> liftIO $ pad <$> readFile temp
247
- ExecBreak {} -> pure $ pad " breakpoints are not supported"
248
+ ExecComplete (Left err) _ -> pure $ pad $ show err
249
+ ExecComplete (Right _) _ -> do
250
+ out <- liftIO $ pad <$> readFile temp
251
+ let forceIt = length out
252
+ return $! forceIt `seq` out
253
+ ExecBreak {} -> pure $ pad " breakpoints are not supported"
248
254
249
255
let changes = [TextEdit editTarget $ T. pack str]
250
256
return changes
251
-
252
257
| isImport df stmt = do
253
- ctxt <- getContext
254
- idecl <- parseImportDecl stmt
255
- setContext $ IIDecl idecl : ctxt
256
- return []
257
-
258
+ ctxt <- getContext
259
+ idecl <- parseImportDecl stmt
260
+ setContext $ IIDecl idecl : ctxt
261
+ return []
258
262
| otherwise = do
259
- void $ runDecls stmt
260
- return []
263
+ void $ runDecls stmt
264
+ return []
261
265
262
266
edits <- liftIO $ evalGhcEnv hscEnv' $ traverse (eval . first T. unpack) statements
263
267
@@ -315,16 +319,3 @@ setupDynFlagsForGHCiLike env dflags = do
315
319
`gopt_set` Opt_IgnoreOptimChanges
316
320
`gopt_set` Opt_IgnoreHpcChanges
317
321
initializePlugins env dflags4
318
-
319
-
320
- withTempFile :: (MonadIO m , MonadMask m ) => (FilePath -> m a ) -> m a
321
- withTempFile k = bracket alloc release (k . fst )
322
- where
323
- alloc = liftIO newTempFile
324
- release = liftIO . snd
325
-
326
- withFile :: (MonadMask m , MonadIO m ) => FilePath -> IOMode -> (Handle -> m b ) -> m b
327
- withFile f mode = bracket alloc release
328
- where
329
- alloc = liftIO $ openFile f mode
330
- release = liftIO . hClose
0 commit comments