Skip to content
Merged
Show file tree
Hide file tree
Changes from 6 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
56 changes: 56 additions & 0 deletions hls-plugin-api/bench/Main.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,56 @@
-- A benchmark comparing the performance characteristics of list-based
-- vs RangeMap-based "in-range filtering" approaches
module Main (main) where

import Control.DeepSeq (force)
import Control.Exception (evaluate)
import Control.Monad (replicateM)
import qualified Criterion
import qualified Criterion.Main
import Data.Random (RVar)
import qualified Data.Random as Fu
import qualified Ide.Plugin.RangeMap as RangeMap
import Language.LSP.Types (Position (..), Range (..), UInt,
isSubrangeOf)
import qualified System.Random.Stateful as Random


genRangeList :: Int -> RVar [Range]
genRangeList n = replicateM n genRange

genRange :: RVar Range
genRange = do
x1 <- genPosition
delta <- genRangeLength
let x2 = x1 { _character = _character x1 + delta }
pure $ Range x1 x2
where
genRangeLength :: RVar UInt
genRangeLength = fromInteger <$> Fu.uniform 5 50

genPosition :: RVar Position
genPosition = Position
<$> (fromInteger <$> Fu.uniform 0 10000)
<*> (fromInteger <$> Fu.uniform 0 150)

filterRangeList :: Range -> [Range] -> [Range]
filterRangeList r = filter (isSubrangeOf r)

main :: IO ()
main = do
rangeLists@[rangeList100, rangeList1000, rangeList10000]
<- traverse (Fu.sampleFrom Random.globalStdGen . genRangeList) [100, 1000, 10000]
[rangeMap100, rangeMap1000, rangeMap10000] <- evaluate $ force $ map (RangeMap.fromList id) rangeLists
targetRange <- Fu.sampleFrom Random.globalStdGen genRange
Criterion.Main.defaultMain
[ Criterion.bgroup "List"
[ Criterion.bench "Size 100" $ Criterion.nf (filterRangeList targetRange) rangeList100
, Criterion.bench "Size 1000" $ Criterion.nf (filterRangeList targetRange) rangeList1000
, Criterion.bench "Size 10000" $ Criterion.nf (filterRangeList targetRange) rangeList10000
]
, Criterion.bgroup "RangeMap"
[ Criterion.bench "Size 100" $ Criterion.nf (RangeMap.filterByRange targetRange) rangeMap100
, Criterion.bench "Size 1000" $ Criterion.nf (RangeMap.filterByRange targetRange) rangeMap1000
, Criterion.bench "Size 10000" $ Criterion.nf (RangeMap.filterByRange targetRange) rangeMap10000
]
]
19 changes: 19 additions & 0 deletions hls-plugin-api/hls-plugin-api.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -29,6 +29,7 @@ library
Ide.Plugin.Config
Ide.Plugin.ConfigUtils
Ide.Plugin.Properties
Ide.Plugin.RangeMap
Ide.PluginUtils
Ide.Types

Expand Down Expand Up @@ -57,6 +58,7 @@ library
, transformers
, unordered-containers
, megaparsec > 9
, hw-fingertree
Copy link
Collaborator

Choose a reason for hiding this comment

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

I'm not keen on adding new dependencies to his-plugin-api. Other alternatives worth considering:

  • Extract RangeMap to a standalone package
  • Leave it in its current home - plugins can depend on each other just fine

Copy link
Collaborator Author

Choose a reason for hiding this comment

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

Although I think the functionality is pretty small to warrant a standalone package, I think I can do that. I am not too keen on the second option. Even if the plugins can depend on each other, I think having this as part of a specific plugin signals the idea that this is something specific to that plugin. I think that may discourage plugin authors to use it (it certainly would discourage me).

What is the downside of adding new dependencies to hls-plugin-api?

Copy link
Collaborator

Choose a reason for hiding this comment

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

What is the downside of adding new dependencies to hls-plugin-api?

When we update HLS for a new version of GHC, hls-plugin-api is one of the packages that needs to get updated if we are to do anything. We are frequently blocked by upstream dependencies not working with the new version of GHC; every new dependency that we add to key packages is another opportunity for that to happen...

Copy link
Collaborator

Choose a reason for hiding this comment

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

That said, hw-fingertree depends only on base, which is promising.

Copy link
Collaborator Author

Choose a reason for hiding this comment

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

I see. Indeed, I had to add GHC 9.4 support to hw-fingertree myself, so I can definitely see that happening 😅 Then I will extract this into a separate small package.

Copy link
Collaborator

Choose a reason for hiding this comment

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

Personally I suggest extracting it to a module in hls-plugin-api or something. Having a whole other package is a pain in its own right!

Also, if it would require approximately the same amount of code as is in hw-fingertree then we may not benefit much.

Here's a compromise thought: since RangeMap is exactly supposed to be a faster alternative to a list-based approach, what if we add a cabal flag to hls-plugin-api use-fingertree, such that if it is on, RangeMap is backed by a fingertree, and if it is off, RangeMap is backed by a list. Then we can turn it off for newer GHC versions until we get a working hw-fingertree?

Copy link
Collaborator Author

Choose a reason for hiding this comment

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

Personally I suggest extracting it to a module in hls-plugin-api or something.

I am a bit confused by this. Do you suggest something other than what currently is present in the PR? Because it currently is a module within hls-plugin-api (unless there is a separate concept of module which I'm not aware).

what if we add a cabal flag to hls-plugin-api use-fingertree

Sounds good to me. What do you think @pepeiborra?

Copy link
Collaborator

Choose a reason for hiding this comment

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

Ah, I think I misunderstood. I thought we were talking about extracting the fingertree code from hw-fingertree so we controlled it, rather than extracting RangeMap. Ignore me, then.

what if we add a cabal flag to hls-plugin-api use-fingertree

... but I still think this is the cleanest solution.

Copy link
Collaborator Author

Choose a reason for hiding this comment

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

I have put the fingertree implementation behind a flag. All related tests (tests of RangeMap itself and the plugins that make use of it) pass with both implementations. Can you take another look to see if it reflects what you had in mind? @michaelpj


if os(windows)
build-depends: Win32
Expand Down Expand Up @@ -92,5 +94,22 @@ test-suite tests
, tasty
, tasty-hunit
, tasty-rerun
, tasty-quickcheck
, text
, lsp-types
, containers

benchmark rangemap-benchmark
type: exitcode-stdio-1.0
default-language: Haskell2010
hs-source-dirs: bench
main-is: Main.hs
ghc-options: -threaded -Wall
build-depends:
base
, hls-plugin-api
, lsp-types
, criterion
, random
, random-fu
, deepseq
44 changes: 44 additions & 0 deletions hls-plugin-api/src/Ide/Plugin/RangeMap.hs
Original file line number Diff line number Diff line change
@@ -0,0 +1,44 @@
{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}

-- | A map that allows fast \"in-range\" filtering. 'RangeMap' is meant
-- to be constructed once and cached as part of a Shake rule. If
-- not, the map will be rebuilt upon each invocation, yielding slower
-- results compared to the list-based approach!
module Ide.Plugin.RangeMap
( RangeMap(..),
fromList,
fromList',
filterByRange,
) where

import Data.Bifunctor (first)
import Data.Foldable (foldl')
import Development.IDE.Graph.Classes (NFData)
import qualified HaskellWorks.Data.IntervalMap.FingerTree as IM
import Language.LSP.Types (Position,
Range (Range))

-- | A map from code ranges to values.
newtype RangeMap a = RangeMap
{ unRangeMap :: IM.IntervalMap Position a
-- ^ 'IM.Interval' of 'Position' corresponds to a 'Range'
}
deriving newtype (NFData)

-- | Construct a 'RangeMap' from a 'Range' accessor and a list of values.
fromList :: (a -> Range) -> [a] -> RangeMap a
fromList extractRange = fromList' . map (\x -> (extractRange x, x))

fromList' :: [(Range, a)] -> RangeMap a
fromList' = RangeMap . toIntervalMap . map (first rangeToInterval)
where
toIntervalMap :: Ord v => [(IM.Interval v, a)] -> IM.IntervalMap v a
toIntervalMap = foldl' (\m (i, v) -> IM.insert i v m) IM.empty

-- | Filter a 'RangeMap' by a given 'Range'.
filterByRange :: Range -> RangeMap a -> [a]
filterByRange range = map snd . IM.dominators (rangeToInterval range) . unRangeMap

rangeToInterval :: Range -> IM.Interval Position
rangeToInterval (Range s e) = IM.Interval s e
43 changes: 39 additions & 4 deletions hls-plugin-api/test/Ide/PluginUtilsTest.hs
Original file line number Diff line number Diff line change
@@ -1,19 +1,27 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}

module Ide.PluginUtilsTest
( tests
) where

import Data.Char (isPrint)
import qualified Data.Text as T
import Ide.PluginUtils (positionInRange, unescape)
import Language.LSP.Types (Position (Position), Range (Range))
import Data.Char (isPrint)
import qualified Data.Set as Set
import qualified Data.Text as T
import qualified Ide.Plugin.RangeMap as RangeMap
import Ide.PluginUtils (positionInRange, unescape)
import Language.LSP.Types (Position (..), Range (Range), UInt,
isSubrangeOf)
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck

tests :: TestTree
tests = testGroup "PluginUtils"
[ unescapeTest
, localOption (QuickCheckMaxSize 10000) $
testProperty "RangeMap-List filtering identical" $
prop_rangemapListEq @Int
]

unescapeTest :: TestTree
Expand All @@ -33,3 +41,30 @@ unescapeTest = testGroup "unescape"
, testCase "control characters should not be escaped" $
unescape "\"\\n\\t\"" @?= "\"\\n\\t\""
]

genRange :: Gen Range
genRange = do
x1 <- genPosition
delta <- genRangeLength
let x2 = x1 { _character = _character x1 + delta }
pure $ Range x1 x2
where
genRangeLength :: Gen UInt
genRangeLength = fromInteger <$> chooseInteger (5, 50)

genPosition :: Gen Position
genPosition = Position
<$> (fromInteger <$> chooseInteger (0, 1000))
<*> (fromInteger <$> chooseInteger (0, 150))

instance Arbitrary Range where
arbitrary = genRange

prop_rangemapListEq :: (Show a, Eq a, Ord a) => Range -> [(Range, a)] -> Property
prop_rangemapListEq r xs =
let filteredList = (map snd . filter (isSubrangeOf r . fst)) xs
filteredRangeMap = RangeMap.filterByRange r (RangeMap.fromList' xs)
in classify (null filteredList) "no matches" $
cover 5 (length filteredList == 1) "1 match" $
cover 2 (length filteredList > 1) ">1 matches" $
Set.fromList filteredList === Set.fromList filteredRangeMap
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,8 @@ import Ide.Plugin.Conversion (AlternateFormat,
ExtensionNeeded (NeedsExtension, NoExtension),
alternateFormat)
import Ide.Plugin.Literals
import Ide.Plugin.RangeMap (RangeMap)
import qualified Ide.Plugin.RangeMap as RangeMap
import Ide.PluginUtils (getNormalizedFilePath,
handleMaybeM, pluginResponse)
import Ide.Types
Expand Down Expand Up @@ -52,7 +54,7 @@ instance NFData CollectLiterals
type instance RuleResult CollectLiterals = CollectLiteralsResult

data CollectLiteralsResult = CLR
{ literals :: [Literal]
{ literals :: RangeMap Literal
Copy link
Collaborator

Choose a reason for hiding this comment

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

nice

, enabledExtensions :: [GhcExtension]
} deriving (Generic)

Expand All @@ -73,25 +75,22 @@ collectLiteralsRule recorder = define (cmapWithPrio LogShake recorder) $ \Collec
let exts = map GhcExtension . getExtensions <$> pm
-- collect all the literals for a file
lits = collectLiterals . pm_parsed_source <$> pm
pure ([], CLR <$> lits <*> exts)
litMap = RangeMap.fromList (realSrcSpanToRange . getSrcSpan) <$> lits
pure ([], CLR <$> litMap <*> exts)

codeActionHandler :: PluginMethodHandler IdeState 'TextDocumentCodeAction
codeActionHandler state pId (CodeActionParams _ _ docId currRange _) = pluginResponse $ do
nfp <- getNormalizedFilePath (docId ^. L.uri)
CLR{..} <- requestLiterals pId state nfp
pragma <- getFirstPragma pId state nfp
-- remove any invalid literals (see validTarget comment)
let litsInRange = filter inCurrentRange literals
let litsInRange = RangeMap.filterByRange currRange literals
-- generate alternateFormats and zip with the literal that generated the alternates
literalPairs = map (\lit -> (lit, alternateFormat lit)) litsInRange
-- make a code action for every literal and its' alternates (then flatten the result)
actions = concatMap (\(lit, alts) -> map (mkCodeAction nfp lit enabledExtensions pragma) alts) literalPairs
pure $ List actions
where
inCurrentRange :: Literal -> Bool
inCurrentRange lit = let srcSpan = getSrcSpan lit
in currRange `contains` srcSpan

mkCodeAction :: NormalizedFilePath -> Literal -> [GhcExtension] -> NextPragmaInfo -> AlternateFormat -> Command |? CodeAction
mkCodeAction nfp lit enabled npi af@(alt, ext) = InR CodeAction {
_title = mkCodeActionTitle lit af enabled
Expand Down Expand Up @@ -127,13 +126,6 @@ mkCodeActionTitle lit (alt, ext) ghcExts
needsExtension :: Extension -> [GhcExtension] -> Bool
needsExtension ext ghcExts = ext `notElem` map unExt ghcExts

-- from HaddockComments.hs
contains :: Range -> RealSrcSpan -> Bool
contains Range {_start, _end} x = isInsideRealSrcSpan _start x || isInsideRealSrcSpan _end x

isInsideRealSrcSpan :: Position -> RealSrcSpan -> Bool
p `isInsideRealSrcSpan` r = let (Range sp ep) = realSrcSpanToRange r in sp <= p && p <= ep

requestLiterals :: MonadIO m => PluginId -> IdeState -> NormalizedFilePath -> ExceptT String m CollectLiteralsResult
requestLiterals (PluginId pId) state = handleMaybeM "Could not Collect Literals"
. liftIO
Expand Down
2 changes: 1 addition & 1 deletion plugins/hls-alternate-number-format-plugin/test/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,7 @@ test :: TestTree
test = testGroup "alternateNumberFormat" [
codeActionHex "TIntDtoH" 3 13
, codeActionOctal "TIntDtoO" 3 13
, codeActionBinary "TIntDtoB" 4 12
, codeActionBinary "TIntDtoB" 4 13
Copy link
Collaborator

Choose a reason for hiding this comment

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

what happened here?

Copy link
Collaborator

Choose a reason for hiding this comment

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

Shouldn't cause any worries, it's just the column number to run the code action. I think the column number is arbitrarily in the middle of a number. Looks like it just matches the other test cases.

, codeActionNumDecimal "TIntDtoND" 5 13
, codeActionFracExp "TFracDtoE" 3 13
, codeActionFloatHex "TFracDtoHF" 4 13
Expand Down
Original file line number Diff line number Diff line change
Expand Up @@ -38,7 +38,6 @@ library
, transformers
, ghc-boot-th
, unordered-containers
, hw-fingertree
hs-source-dirs: src
default-language: Haskell2010

Expand Down
Loading