Skip to content

Commit 7ccdeb9

Browse files
authored
eval: more robust way to extract comments from ParsedModule (#4113)
1 parent 5502b76 commit 7ccdeb9

File tree

4 files changed

+28
-28
lines changed

4 files changed

+28
-28
lines changed

plugins/hls-eval-plugin/src/Ide/Plugin/Eval/Rules.hs

Lines changed: 14 additions & 28 deletions
Original file line numberDiff line numberDiff line change
@@ -1,13 +1,13 @@
11
{-# LANGUAGE CPP #-}
22
{-# LANGUAGE LambdaCase #-}
33
{-# LANGUAGE PatternSynonyms #-}
4-
{-# LANGUAGE RecordWildCards #-}
54

6-
-- To avoid warning "Pattern match has inaccessible right hand side"
7-
{-# OPTIONS_GHC -Wno-overlapping-patterns #-}
85
module Ide.Plugin.Eval.Rules (GetEvalComments(..), rules,queueForEvaluation, unqueueForEvaluation, Log) where
96

7+
import Control.Lens (toListOf)
108
import Control.Monad.IO.Class (MonadIO (liftIO))
9+
import qualified Data.ByteString as BS
10+
import Data.Data.Lens (biplate)
1111
import Data.HashSet (HashSet)
1212
import qualified Data.HashSet as Set
1313
import Data.IORef
@@ -24,8 +24,7 @@ import Development.IDE (GetModSummaryWithoutTimes
2424
fromNormalizedFilePath,
2525
msrModSummary,
2626
realSrcSpanToRange,
27-
useWithStale_,
28-
use_)
27+
useWithStale_, use_)
2928
import Development.IDE.Core.PositionMapping (toCurrentRange)
3029
import Development.IDE.Core.Rules (computeLinkableTypeForDynFlags,
3130
needsCompilationRule)
@@ -39,14 +38,12 @@ import Development.IDE.GHC.Compat
3938
import qualified Development.IDE.GHC.Compat as SrcLoc
4039
import qualified Development.IDE.GHC.Compat.Util as FastString
4140
import Development.IDE.Graph (alwaysRerun)
42-
import Ide.Logger (Pretty (pretty),
41+
import GHC.Parser.Annotation
42+
import Ide.Logger (Pretty (pretty),
4343
Recorder, WithPriority,
4444
cmapWithPrio)
45-
import GHC.Parser.Annotation
4645
import Ide.Plugin.Eval.Types
4746

48-
import qualified Data.ByteString as BS
49-
5047
newtype Log = LogShake Shake.Log deriving Show
5148

5249
instance Pretty Log where
@@ -74,28 +71,17 @@ unqueueForEvaluation ide nfp = do
7471
-- remove the module from the Evaluating state, so that next time it won't evaluate to True
7572
atomicModifyIORef' var $ \fs -> (Set.delete nfp fs, ())
7673

77-
#if MIN_VERSION_ghc(9,5,0)
78-
getAnnotations :: Development.IDE.GHC.Compat.Located (HsModule GhcPs) -> [LEpaComment]
79-
getAnnotations (L _ m@(HsModule { hsmodExt = XModulePs {hsmodAnn = anns'}})) =
80-
#else
81-
getAnnotations :: Development.IDE.GHC.Compat.Located HsModule -> [LEpaComment]
82-
getAnnotations (L _ m@(HsModule { hsmodAnn = anns'})) =
83-
#endif
84-
priorComments annComments <> getFollowingComments annComments
85-
<> concatMap getCommentsForDecl (hsmodImports m)
86-
<> concatMap getCommentsForDecl (hsmodDecls m)
87-
where
88-
annComments = epAnnComments anns'
89-
90-
getCommentsForDecl :: GenLocated (SrcSpanAnn' (EpAnn ann)) e
91-
-> [LEpaComment]
92-
getCommentsForDecl (L (SrcSpanAnn (EpAnn _ _ cs) _) _) = priorComments cs <> getFollowingComments cs
93-
getCommentsForDecl (L (SrcSpanAnn (EpAnnNotUsed) _) _) = []
94-
9574
apiAnnComments' :: ParsedModule -> [SrcLoc.RealLocated EpaCommentTok]
9675
apiAnnComments' pm = do
97-
L span (EpaComment c _) <- getAnnotations $ pm_parsed_source pm
76+
L span (EpaComment c _) <- getEpaComments $ pm_parsed_source pm
9877
pure (L (anchor span) c)
78+
where
79+
#if MIN_VERSION_ghc(9,5,0)
80+
getEpaComments :: Development.IDE.GHC.Compat.Located (HsModule GhcPs) -> [LEpaComment]
81+
#else
82+
getEpaComments :: Development.IDE.GHC.Compat.Located HsModule -> [LEpaComment]
83+
#endif
84+
getEpaComments = toListOf biplate
9985

10086
pattern RealSrcSpanAlready :: SrcLoc.RealSrcSpan -> SrcLoc.RealSrcSpan
10187
pattern RealSrcSpanAlready x = x

plugins/hls-eval-plugin/test/Main.hs

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -112,6 +112,7 @@ tests =
112112
, goldenWithEval ":kind treats a multilined result properly" "T25" "hs"
113113
, goldenWithEvalAndFs "local imports" (FS.directProjectMulti ["T26.hs", "Util.hs"]) "T26" "hs"
114114
, goldenWithEval "Preserves one empty comment line after prompt" "T27" "hs"
115+
, goldenWithEval "Evaluate comment after multiline function definition" "T28" "hs"
115116
, goldenWithEval "Multi line comments" "TMulti" "hs"
116117
, goldenWithEval "Multi line comments, with the last test line ends without newline" "TEndingMulti" "hs"
117118
, goldenWithEval "Evaluate expressions in Plain comments in both single line and multi line format" "TPlainComment" "hs"
Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,7 @@
1+
module T28 where
2+
3+
f True = True
4+
f False = False
5+
6+
-- >>> 1+1
7+
-- 2
Lines changed: 6 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,6 @@
1+
module T28 where
2+
3+
f True = True
4+
f False = False
5+
6+
-- >>> 1+1

0 commit comments

Comments
 (0)