Skip to content

Commit

Permalink
Compitable fix
Browse files Browse the repository at this point in the history
  • Loading branch information
July541 committed May 24, 2022
1 parent 4882005 commit 8e856d0
Show file tree
Hide file tree
Showing 5 changed files with 7 additions and 10 deletions.
4 changes: 0 additions & 4 deletions ghcide/src/Development/IDE/GHC/Compat/Core.hs
Original file line number Diff line number Diff line change
Expand Up @@ -840,8 +840,6 @@ pattern L l a <- GHC.L (getLoc -> l) a
type HasSrcSpan = SrcLoc.HasSrcSpan
getLoc :: SrcLoc.HasSrcSpan a => a -> SrcLoc.SrcSpan
getLoc = SrcLoc.getLoc
instance HasSrcSpan SrcLoc.SrcSpan where
Development.IDE.GHC.Compat.Core.getLoc = id

#else

Expand All @@ -851,8 +849,6 @@ instance HasSrcSpan Name where
getLoc = nameSrcSpan
instance HasSrcSpan (SrcLoc.GenLocated SrcSpan a) where
getLoc = SrcLoc.getLoc
instance HasSrcSpan SrcSpan where
getLoc = id

#endif

Expand Down
3 changes: 2 additions & 1 deletion plugins/hls-class-plugin/src/Ide/Plugin/Class/CodeAction.hs
Original file line number Diff line number Diff line change
Expand Up @@ -5,6 +5,7 @@

module Ide.Plugin.Class.CodeAction where

import Control.Applicative
import Control.Lens hiding (List, use)
import Control.Monad.Extra
import Control.Monad.IO.Class (liftIO)
Expand Down Expand Up @@ -178,7 +179,7 @@ minDefToMethodGroups range sigs = go
where
go (Var mn) = [[ (T.pack . occNameString . occName $ mn, bindRendered sig)
| sig <- sigs
, inRange range (getSrcSpan (bindName sig))
, inRange range (getSrcSpan $ bindName sig)
, printOutputable mn == T.drop (T.length bindingPrefix) (printOutputable (bindName sig))
]]
go (Or ms) = concatMap (go . unLoc) ms
Expand Down
4 changes: 2 additions & 2 deletions plugins/hls-class-plugin/src/Ide/Plugin/Class/CodeLens.hs
Original file line number Diff line number Diff line change
Expand Up @@ -86,8 +86,8 @@ codeLens state plId CodeLensParams{..} = do
-- Existed signatures' name
sigNames = concat $ mapMaybe (\(L _ r) -> getSigName r) cid_sigs
toBindInfo (L l (L l' _)) = BindInfo
(getLoc l) -- bindSpan
(getLoc l') -- bindNameSpan
(locA l) -- bindSpan
(locA l') -- bindNameSpan
in toBindInfo <$> filter (\(L _ name) -> unLoc name `notElem` sigNames) bindNames
getBindSpanWithoutSig _ = []

Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -118,5 +118,5 @@ addMethodDecls ps mDecls range withSig = do
foldM (insertAfter d) ps (reverse decls)

findInstDecl :: ParsedSource -> Range -> Transform (LHsDecl GhcPs)
findInstDecl ps range = head . filter (inRange range) <$> hsDecls ps
findInstDecl ps range = head . filter (inRange range . getLoc) <$> hsDecls ps
#endif
4 changes: 2 additions & 2 deletions plugins/hls-class-plugin/src/Ide/Plugin/Class/Utils.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,8 +25,8 @@ isBindingName :: Name -> Bool
isBindingName name = isPrefixOf bindingPrefix $ occNameString $ nameOccName name

-- | Check if some `HasSrcSpan` value in the given range
inRange :: HasSrcSpan a => Range -> a -> Bool
inRange range s = maybe False (subRange range) (srcSpanToRange (getLoc s))
inRange :: Range -> SrcSpan -> Bool
inRange range s = maybe False (subRange range) (srcSpanToRange s)

ghostSpan :: RealSrcSpan
ghostSpan = realSrcLocSpan $ mkRealSrcLoc (fsLit "<haskell-language-sever>") 1 1
Expand Down

0 comments on commit 8e856d0

Please sign in to comment.