Skip to content
This repository was archived by the owner on Oct 7, 2020. It is now read-only.

Commit ed080e7

Browse files
authored
Merge pull request #794 from Bubba/777-redux
Remove IdeResponse, split out IdeM into IdeM and IdeDeferM
2 parents cf08220 + 802e543 commit ed080e7

27 files changed

+468
-654
lines changed

app/MainHie.hs

Lines changed: 1 addition & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,14 +1,11 @@
1-
{-# LANGUAGE CPP #-}
21
{-# LANGUAGE OverloadedStrings #-}
32
{-# LANGUAGE RankNTypes #-}
43
module Main where
54

65
import Control.Concurrent.STM.TChan
76
import Control.Monad
87
import Control.Monad.STM
9-
#if __GLASGOW_HASKELL__ < 804
10-
import Data.Semigroup
11-
#endif
8+
import Data.Monoid ((<>))
129
import Data.Version (showVersion)
1310
import qualified GhcMod.Types as GM
1411
import Haskell.Ide.Engine.Dispatcher

docs/Architecture.md

Lines changed: 16 additions & 76 deletions
Original file line numberDiff line numberDiff line change
@@ -33,18 +33,6 @@ data CachedModule = CachedModule
3333
, newPosToOld :: Position -> Maybe Position
3434
, oldPosToNew :: Position -> Maybe Position
3535
}
36-
37-
getCachedModule :: Uri -> IdeM (CachedModuleResult)
38-
39-
-- | The possible states the cache can be in
40-
-- along with the cache or error if present
41-
data CachedModuleResult = ModuleLoading
42-
-- ^ The module has no cache yet and has not failed
43-
| ModuleFailed T.Text
44-
-- ^ The module has no cache but something went wrong
45-
| ModuleCached CachedModule IsStale
46-
-- ^ A cache exists for the module
47-
type IsStale = Bool
4836
```
4937

5038
On every file open or edit, HIE tries to load a `TypecheckedModule`(as defined in the ghc api)
@@ -80,7 +68,8 @@ class Typeable a => ModuleCache a where
8068
cacheDataProducer :: CachedModule -> IdeM a
8169

8270
withCachedModuleAndData :: forall a b. ModuleCache a
83-
=> Uri -> IdeM b -> (CachedModule -> a -> IdeM b) -> IdeM b
71+
=> FilePath -> b
72+
-> (CachedModule -> a -> IdeM b) -> IdeM b
8473
withCachedModuleAndData uri noCache callback = ...
8574
```
8675

@@ -106,7 +95,7 @@ This data is used to find all references to a symbol, and to find the name corre
10695
a particular position in the source.
10796

10897
```haskell
109-
getReferencesInDoc :: Uri -> Position -> IdeM (IdeResponse [J.DocumentHighlight])
98+
getReferencesInDoc :: Uri -> Position -> IdeM (IdeResult [J.DocumentHighlight])
11099
getReferencesInDoc uri pos = do
111100
let noCache = return $ nonExistentCacheErr "getReferencesInDoc"
112101
withCachedModuleAndData uri noCache $
@@ -145,7 +134,7 @@ data GhcRequest m = forall a. GhcRequest
145134
data IdeRequest m = forall a. IdeRequest
146135
{ pureReqId :: J.LspId
147136
, pureReqCallback :: RequestCallback m a
148-
, pureReq :: IdeM (IdeResponse a)
137+
, pureReq :: IdeM (IdeResult a)
149138
}
150139

151140
```
@@ -176,75 +165,26 @@ for handling the "definition" request
176165
...
177166

178167
-- HaRePlugin.hs
179-
findDef :: Uri -> Position -> IdeM (IdeResponse Location)
168+
findDef :: Uri -> Position -> IdeM (IdeResult Location)
180169
```
181170

182171
The request uses the `findDef` function in the `HaRe` plugin to get the `Location`
183172
of the definition of the symbol at the given position. The callback makes a LSP
184173
response message out of the location, and forwards it to thread #4 which sends
185-
it to the IDE via stdout
174+
it to the IDE via stdout.
186175

187-
## Responses and results
176+
## Deferred requests
188177

189-
While working in the `IdeGhcM` thread, you return results back to the dispatcher with
190-
`IdeResult`:
178+
Should you find yourself wanting to access a typechecked module from within `IdeM`,
179+
use `withCachedModule` to get access to a cached version of that module.
180+
If there is no cached module available, then it will automatically defer your result,
181+
or return a default if that then fails to typecheck:
191182

192183
```haskell
193-
runHareCommand :: String -> RefactGhc [ApplyRefacResult]
194-
-> IdeGhcM (IdeResult WorkspaceEdit)
195-
runHareCommand name cmd = do
196-
eitherRes <- runHareCommand' cmd
197-
case eitherRes of
198-
Left err ->
199-
pure (IdeResultFail
200-
(IdeError PluginError
201-
(T.pack $ name <> ": \"" <> err <> "\"")
202-
Null))
203-
Right res -> do
204-
let changes = getRefactorResult res
205-
refactRes <- makeRefactorResult changes
206-
pure (IdeResultOk refactRes)
184+
withCachedModule file (IdeResultOk []) $ \cm -> do
185+
-- poke about with cm here
207186
```
208187

209-
On `IdeM`, you must wrap any `IdeResult` in an `IdeResponse`:
210-
211-
```haskell
212-
getDynFlags :: Uri -> IdeM (IdeResponse DynFlags)
213-
getDynFlags uri =
214-
pluginGetFileResponse "getDynFlags: " uri $ \fp -> do
215-
mcm <- getCachedModule fp
216-
case mcm of
217-
ModuleCached cm _ -> return $
218-
IdeResponseOk $ ms_hspp_opts $ pm_mod_summary $ tm_parsed_module $ tcMod cm
219-
_ -> return $
220-
IdeResponseFail $
221-
IdeError PluginError ("getDynFlags: \"" <> "module not loaded" <> "\"") Null
222-
```
223-
224-
Sometimes a request may need access to the typechecked module from ghc-mod, but
225-
it is desirable to keep it on the `IdeM` thread. For this a deferred response can
226-
be made:
227-
228-
```haskell
229-
getDynFlags :: Uri -> IdeM (IdeResponse DynFlags)
230-
getDynFlags uri =
231-
pluginGetFileResponse "getDynFlags: " uri $ \fp -> do
232-
mcm <- getCachedModule fp
233-
return $ case mcm of
234-
ModuleCached cm _ -> IdeResponseOk $ getFlags cm
235-
_ -> IdeResponseDeferred fp getFlags
236-
where getFlags = ms_hspp_opts $ pm_mod_summary $ tm_parsed_module $ tcMod cm
237-
```
238-
239-
A deferred response takes a file path to a module, and a callback which will be executed
240-
as with the cached module passed as an argument as soon as the module is loaded.
241-
242-
This is wrapped with the helper function `withCachedModule` which will immediately return
243-
the cached module if it is already available to use, and only defer it otherwise.
244-
245-
```haskell
246-
getDynFlags :: Uri -> IdeM (IdeResponse DynFlags)
247-
getDynFlags uri =
248-
pluginGetFileResponse "getDynFlags: " uri $ \fp ->
249-
withCachedModule fp (return . IdeResponseOk . ms_hspp_opts . pm_mod_summary . tm_parsed_module . tcMod)
250-
```
188+
Internally, a deferred response is represented by `IdeDefer`, which takes a file path
189+
to a module, and a callback which will be executed with a `UriCache` passed as an
190+
argument as soon as the module is loaded, or a `UriCacheFailed` if it failed.

haskell-ide-engine.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -159,6 +159,7 @@ test-suite unit-test
159159
, containers
160160
, directory
161161
, filepath
162+
, free
162163
, haskell-lsp
163164
, haskell-ide-engine
164165
-- , hie-test-utils

hie-plugin-api/Haskell/Ide/Engine/GhcModuleCache.hs

Lines changed: 1 addition & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,6 @@
44

55
module Haskell.Ide.Engine.GhcModuleCache where
66

7-
import qualified Data.Text as T
87
import qualified Data.Map as Map
98
import Data.Dynamic (Dynamic)
109
import Data.Typeable (TypeRep)
@@ -22,8 +21,7 @@ type UriCaches = Map.Map FilePath UriCache
2221
data UriCache = UriCache
2322
{ cachedModule :: !CachedModule
2423
, cachedData :: !(Map.Map TypeRep Dynamic)
25-
, isStale :: !Bool
26-
} | UriCacheFailed T.Text deriving Show
24+
} | UriCacheFailed deriving Show
2725

2826
data CachedModule = CachedModule
2927
{ tcMod :: !TypecheckedModule

0 commit comments

Comments
 (0)