Skip to content

Commit 54ece51

Browse files
committed
hlint
1 parent 3eea015 commit 54ece51

File tree

4 files changed

+37
-36
lines changed

4 files changed

+37
-36
lines changed

ghcide/src/Development/IDE/Core/PositionMapping.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -199,7 +199,7 @@ deltaFromDiff (T.lines -> old) (T.lines -> new) =
199199
| otherwise = case V.unsafeIndex xs line of
200200
-1 ->
201201
-- look for the previous and next lines that mapped successfully
202-
let !prev = 1 + (V.unsafeIndex prevs line)
202+
let !prev = 1 + V.unsafeIndex prevs line
203203
!next = V.unsafeIndex nexts line
204204
in PositionRange (Position prev 0) (Position next 0)
205205
line' -> PositionExact (Position line' col)

ghcide/src/Development/IDE/Core/Rules.hs

Lines changed: 33 additions & 31 deletions
Original file line numberDiff line numberDiff line change
@@ -93,7 +93,6 @@ import Data.List
9393
import qualified Data.Set as Set
9494
import qualified Data.Map as M
9595
import qualified Data.Text as T
96-
import qualified Data.Text.IO as T
9796
import qualified Data.Text.Encoding as T
9897
import Development.IDE.GHC.Error
9998
import Development.Shake hiding (Diagnostic)
@@ -119,6 +118,7 @@ import Control.Concurrent.Async (concurrently)
119118
import Control.Monad.Reader
120119
import Control.Exception.Safe
121120

121+
import Data.Coerce
122122
import Control.Monad.State
123123
import FastString (FastString(uniq))
124124
import qualified HeaderInfo as Hdr
@@ -572,15 +572,15 @@ persistentHieFileRule :: Rules ()
572572
persistentHieFileRule = addPersistentRule GetHieAst $ \file -> runMaybeT $ do
573573
res <- readHieFileForSrcFromDisk file
574574
vfs <- asks vfs
575+
encoding <- liftIO getLocaleEncoding
575576
(currentSource,ver) <- liftIO $ do
576577
mvf <- getVirtualFile vfs $ filePathToUri' file
577578
case mvf of
578-
Nothing -> (,Nothing) <$> T.readFile (fromNormalizedFilePath file)
579-
Just vf -> pure $ (Rope.toText $ _text vf, Just $ _lsp_version vf)
580-
encoding <- liftIO $ getLocaleEncoding
579+
Nothing -> (,Nothing) . T.decode encoding <$> BS.readFile (fromNormalizedFilePath file)
580+
Just vf -> pure (Rope.toText $ _text vf, Just $ _lsp_version vf)
581581
let refmap = generateReferencesMap . getAsts . hie_asts $ res
582582
del = deltaFromDiff (T.decode encoding $ hie_hs_src res) currentSource
583-
pure $ (HAR (hie_module res) (hie_asts res) refmap mempty (HieFromDisk res),del,ver)
583+
pure (HAR (hie_module res) (hie_asts res) refmap mempty (HieFromDisk res),del,ver)
584584

585585
getHieAstRuleDefinition :: NormalizedFilePath -> HscEnv -> TcModuleResult -> Action (IdeResult HieAstResult)
586586
getHieAstRuleDefinition f hsc tmr = do
@@ -590,8 +590,9 @@ getHieAstRuleDefinition f hsc tmr = do
590590
isFoi <- use_ IsFileOfInterest f
591591
diagsWrite <- case isFoi of
592592
IsFOI Modified -> do
593-
liftIO $ eventer se $ LSP.NotCustomServer $
594-
LSP.NotificationMessage "2.0" (LSP.CustomServerMethod "ghcide/reference/ready") (toJSON $ fromNormalizedFilePath f)
593+
when (coerce $ ideTesting se) $
594+
liftIO $ eventer se $ LSP.NotCustomServer $
595+
LSP.NotificationMessage "2.0" (LSP.CustomServerMethod "ghcide/reference/ready") (toJSON $ fromNormalizedFilePath f)
595596
pure []
596597
_ | Just asts <- masts -> do
597598
source <- getSourceFileSource f
@@ -817,33 +818,34 @@ getModIfaceFromDiskRule = defineEarlyCutoff $ \GetModIfaceFromDisk f -> do
817818
let fp = hiFileFingerPrint <$> res
818819
return (fp, (diags' <> diags_session, res))
819820

820-
case exists of
821-
-- Don't have a .hie file, must regenerate
822-
False -> regenerateHieFile
821+
if exists
822+
then do
823823
-- Have a hie file, must check if it matches version in db
824-
True -> do
825-
hash <- liftIO $ getFileHash hie_loc
826-
mrow <- liftIO $ HieDb.lookupHieFileFromSource hiedb (fromNormalizedFilePath f)
827-
case mrow of
828-
-- All good, the db has indexed the file
829-
Just row
830-
| hash == HieDb.modInfoHash (HieDb.hieModInfo row)
831-
, hie_loc == HieDb.hieModuleHieFile row -> do
824+
hash <- liftIO $ getFileHash hie_loc
825+
mrow <- liftIO $ HieDb.lookupHieFileFromSource hiedb (fromNormalizedFilePath f)
826+
case mrow of
827+
-- All good, the db has indexed the file
828+
Just row
829+
| hash == HieDb.modInfoHash (HieDb.hieModInfo row)
830+
, hie_loc == HieDb.hieModuleHieFile row -> do
831+
when (coerce $ ideTesting se) $
832832
liftIO $ eventer se $ LSP.NotCustomServer $
833833
LSP.NotificationMessage "2.0" (LSP.CustomServerMethod "ghcide/reference/ready") (toJSON $ fromNormalizedFilePath f)
834-
return (fp, (diags <> diags_session, Just x))
835-
-- Not in db, must re-index
836-
_ -> do
837-
mhf <- liftIO $ runIdeAction "GetModIfaceFromDisk" se $ runMaybeT $
838-
readHieFileFromDisk hie_loc
839-
case mhf of
840-
-- Uh oh, we failed to read the file for some reason, need to regenerate it
841-
Nothing -> regenerateHieFile
842-
-- can just re-index the file we read from disk
843-
Just hf -> liftIO $ do
844-
L.logInfo (logger se) $ "Re-indexing hie file for" <> T.pack (show (f,hash,fmap (HieDb.modInfoHash . HieDb.hieModInfo) mrow))
845-
indexHieFile se ms f hash hf
846-
return (fp, (diags <> diags_session, Just x))
834+
return (fp, (diags <> diags_session, Just x))
835+
-- Not in db, must re-index
836+
_ -> do
837+
mhf <- liftIO $ runIdeAction "GetModIfaceFromDisk" se $ runMaybeT $
838+
readHieFileFromDisk hie_loc
839+
case mhf of
840+
-- Uh oh, we failed to read the file for some reason, need to regenerate it
841+
Nothing -> regenerateHieFile
842+
-- can just re-index the file we read from disk
843+
Just hf -> liftIO $ do
844+
L.logInfo (logger se) $ "Re-indexing hie file for" <> T.pack (show (f,hash,fmap (HieDb.modInfoHash . HieDb.hieModInfo) mrow))
845+
indexHieFile se ms f hash hf
846+
return (fp, (diags <> diags_session, Just x))
847+
-- Don't have a .hie file, must regenerate
848+
else regenerateHieFile
847849

848850
isHiFileStableRule :: Rules ()
849851
isHiFileStableRule = defineEarlyCutoff $ \IsHiFileStable f -> do

ghcide/src/Development/IDE/Spans/AtPoint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -72,7 +72,7 @@ computeTypeReferences = foldr (\ast m -> M.unionWith (++) (go ast) m) M.empty
7272
this = M.fromListWith (++)
7373
$ map (, [nodeSpan ast])
7474
$ concatMap namesInType
75-
$ mapMaybe (\x -> guard (any (not . isOccurrence) (identInfo x)) *> identType x)
75+
$ mapMaybe (\x -> guard (not $ all isOccurrence $ identInfo x) *> identType x)
7676
$ M.elems
7777
$ nodeIdentifiers $ nodeInfo ast
7878

ghcide/test/exe/Main.hs

Lines changed: 2 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -4198,7 +4198,7 @@ getReferences' (file, l, c) includeDeclaration = do
41984198

41994199
referenceTestSession :: String -> FilePath -> [FilePath] -> (FilePath -> Session ()) -> TestTree
42004200
referenceTestSession name thisDoc docs' f = testSessionWithExtraFiles "references" name $ \dir -> do
4201-
let docs = map (dir </>) $ delete thisDoc $ nub $ docs'
4201+
let docs = map (dir </>) $ delete thisDoc $ nubOrd docs'
42024202
-- Initial Index
42034203
docid <- openDoc thisDoc "haskell"
42044204
let
@@ -4207,8 +4207,7 @@ referenceTestSession name thisDoc docs' f = testSessionWithExtraFiles "reference
42074207
doc <- skipManyTill anyMessage $ satisfyMaybe $ \case
42084208
NotCustomServer (NotificationMessage _ (CustomServerMethod "ghcide/reference/ready") fp) -> do
42094209
A.Success fp' <- pure $ fromJSON fp
4210-
doc <- find (fp' ==) docs
4211-
pure doc
4210+
find (fp' ==) docs
42124211
_ -> Nothing
42134212
loop (delete doc docs)
42144213
loop docs

0 commit comments

Comments
 (0)