Skip to content
This repository was archived by the owner on Jan 2, 2021. It is now read-only.
Merged
Show file tree
Hide file tree
Changes from all commits
Commits
File filter

Filter by extension

Filter by extension

Conversations
Failed to load comments.
Loading
Jump to
Jump to file
Failed to load files.
Loading
Diff view
Diff view
3 changes: 2 additions & 1 deletion session-loader/Development/IDE/Session.hs
Original file line number Diff line number Diff line change
Expand Up @@ -64,6 +64,7 @@ import Linker
import Module
import NameCache
import Packages
import Control.Exception (evaluate)

-- | Given a root directory, return a Shake 'Action' which setups an
-- 'IdeGhcSession' given a file.
Expand Down Expand Up @@ -312,7 +313,7 @@ loadSession dir = do
-- update xports map
extras <- getShakeExtras
let !exportsMap' = createExportsMap $ mapMaybe (fmap hirModIface) modIfaces
liftIO $ modifyVar_ (exportsMap extras) $ return . (exportsMap' <>)
liftIO $ modifyVar_ (exportsMap extras) $ evaluate . (exportsMap' <>)
Copy link
Collaborator

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

Definitely! We should probably add an HLint rule for this - or wrap modifyVar_ into modifyVar_' and only use those.

Copy link
Collaborator Author

Choose a reason for hiding this comment

The reason will be displayed to describe this comment to others. Learn more.

An hlint rule would be great

pure opts

-- | Run the specific cradle on a specific FilePath via hie-bios.
Expand Down
2 changes: 1 addition & 1 deletion src/Development/IDE/Core/OfInterest.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,6 +99,6 @@ kick = mkDelayedAction "kick" Debug $ do
ShakeExtras{exportsMap} <- getShakeExtras
let modIfaces = mapMaybe (fmap (hm_iface . tmrModInfo)) results
!exportsMap' = createExportsMap modIfaces
liftIO $ modifyVar_ exportsMap $ return . (exportsMap' <>)
liftIO $ modifyVar_ exportsMap $ evaluate . (exportsMap' <>)

liftIO $ progressUpdate KickCompleted
2 changes: 1 addition & 1 deletion src/Development/IDE/Core/Shake.hs
Original file line number Diff line number Diff line change
Expand Up @@ -413,7 +413,7 @@ shakeOpen getLspId eventer withProgress withIndefiniteProgress logger debouncer
progressAsync <- async $
when reportProgress $
progressThread mostRecentProgressEvent inProgress
exportsMap <- newVar HMap.empty
exportsMap <- newVar mempty

actionQueue <- newQueue

Expand Down
5 changes: 3 additions & 2 deletions src/Development/IDE/Plugin/CodeAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -59,6 +59,7 @@ import Control.Applicative ((<|>))
import Safe (atMay)
import Bag (isEmptyBag)
import Control.Concurrent.Extra (readVar)
import qualified Data.HashSet as Set

plugin :: Plugin c
plugin = codeActionPluginWithRules rules codeAction <> Plugin mempty setHandlersCodeLens
Expand All @@ -85,7 +86,7 @@ codeAction lsp state (TextDocumentIdentifier uri) _range CodeActionContext{_diag
-- This is quite expensive 0.6-0.7s on GHC
pkgExports <- runAction "CodeAction:PackageExports" state $ (useNoFile_ . PackageExports) `traverse` env
localExports <- readVar (exportsMap $ shakeExtras state)
let exportsMap = Map.unionWith (<>) localExports (fromMaybe mempty pkgExports)
let exportsMap = localExports <> fromMaybe mempty pkgExports
let dflags = hsc_dflags . hscEnv <$> env
pure $ Right
[ CACodeAction $ CodeAction title (Just CodeActionQuickFix) (Just $ List [x]) (Just edit) Nothing
Expand Down Expand Up @@ -881,7 +882,7 @@ constructNewImportSuggestions
:: ExportsMap -> NotInScope -> Maybe [T.Text] -> [T.Text]
constructNewImportSuggestions exportsMap thingMissing notTheseModules = nubOrd
[ suggestion
| (identInfo, m) <- fromMaybe [] $ Map.lookup name exportsMap
| (identInfo, m) <- maybe [] Set.toList $ Map.lookup name (getExportsMap exportsMap)
, canUseIdent thingMissing identInfo
, m `notElem` fromMaybe [] notTheseModules
, suggestion <- renderNewImport identInfo m
Expand Down
20 changes: 16 additions & 4 deletions src/Development/IDE/Types/Exports.hs
Original file line number Diff line number Diff line change
@@ -1,7 +1,9 @@
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DerivingStrategies #-}
module Development.IDE.Types.Exports
(
IdentInfo(..),
ExportsMap,
ExportsMap(..),
createExportsMap,
) where

Expand All @@ -16,8 +18,17 @@ import Name
import FieldLabel (flSelector)
import qualified Data.HashMap.Strict as Map
import GhcPlugins (IfaceExport)
import Data.HashSet (HashSet)
import qualified Data.HashSet as Set
import Data.Bifunctor (Bifunctor(second))
import Data.Hashable (Hashable)

type ExportsMap = HashMap IdentifierText [(IdentInfo,ModuleNameText)]
newtype ExportsMap = ExportsMap
{getExportsMap :: HashMap IdentifierText (HashSet (IdentInfo,ModuleNameText))}
deriving newtype (Monoid, NFData, Show)

instance Semigroup ExportsMap where
ExportsMap a <> ExportsMap b = ExportsMap $ Map.unionWith (<>) a b

type IdentifierText = Text
type ModuleNameText = Text
Expand All @@ -29,6 +40,7 @@ data IdentInfo = IdentInfo
, isDatacon :: !Bool
}
deriving (Eq, Generic, Show)
deriving anyclass Hashable

instance NFData IdentInfo

Expand All @@ -51,9 +63,9 @@ mkIdentInfos (AvailTC _ nn flds)
]

createExportsMap :: [ModIface] -> ExportsMap
createExportsMap = Map.fromListWith (++) . concatMap doOne
createExportsMap = ExportsMap . Map.fromListWith (<>) . concatMap doOne
where
doOne mi = concatMap (unpackAvail mn) (mi_exports mi)
doOne mi = concatMap (fmap (second Set.fromList) . unpackAvail mn) (mi_exports mi)
where
mn = moduleName $ mi_module mi

Expand Down