Skip to content

Commit a41954e

Browse files
authored
Merge pull request #444 from kokobd/master
add subRange and positionInRange
2 parents 184dae1 + 0b1da22 commit a41954e

File tree

2 files changed

+50
-7
lines changed

2 files changed

+50
-7
lines changed

lsp-types/src/Language/LSP/Types/Location.hs

Lines changed: 15 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -1,11 +1,11 @@
1-
{-# LANGUAGE TemplateHaskell #-}
2-
{-# LANGUAGE DeriveGeneric #-}
1+
{-# LANGUAGE DeriveGeneric #-}
2+
{-# LANGUAGE TemplateHaskell #-}
33
module Language.LSP.Types.Location where
44

55
import Control.DeepSeq
66
import Data.Aeson.TH
77
import Data.Hashable
8-
import GHC.Generics hiding (UInt)
8+
import GHC.Generics hiding (UInt)
99
import Language.LSP.Types.Common
1010
import Language.LSP.Types.Uri
1111
import Language.LSP.Types.Utils
@@ -33,8 +33,8 @@ instance Hashable Position
3333

3434
data Range =
3535
Range
36-
{ _start :: Position -- ^ The range's start position.
37-
, _end :: Position -- ^ The range's end position.
36+
{ _start :: Position -- ^ The range's start position. (inclusive)
37+
, _end :: Position -- ^ The range's end position. (exclusive, see: https://microsoft.github.io/language-server-protocol/specifications/lsp/3.17/specification/#range )
3838
} deriving (Show, Read, Eq, Ord, Generic)
3939

4040
instance NFData Range
@@ -65,12 +65,12 @@ data LocationLink =
6565
-- range at the mouse position.
6666
_originSelectionRange :: Maybe Range
6767
-- | The target resource identifier of this link.
68-
, _targetUri :: Uri
68+
, _targetUri :: Uri
6969
-- | The full target range of this link. If the target for example is a
7070
-- symbol then target range is the range enclosing this symbol not including
7171
-- leading/trailing whitespace but everything else like comments. This
7272
-- information is typically used to highlight the range in the editor.
73-
, _targetRange :: Range
73+
, _targetRange :: Range
7474
-- | The range that should be selected and revealed when this link is being
7575
-- followed, e.g the name of a function. Must be contained by the the
7676
-- 'targetRange'. See also @DocumentSymbol._range@
@@ -84,3 +84,11 @@ deriveJSON lspOptions ''LocationLink
8484
-- prop> mkRange l c l' c' = Range (Position l c) (Position l' c')
8585
mkRange :: UInt -> UInt -> UInt -> UInt -> Range
8686
mkRange l c l' c' = Range (Position l c) (Position l' c')
87+
88+
-- | 'isSubrangeOf' returns true if for every 'Position' in the first 'Range', it's also in the second 'Range'.
89+
isSubrangeOf :: Range -> Range -> Bool
90+
isSubrangeOf smallRange range = _start smallRange >= _start range && _end smallRange <= _end range
91+
92+
-- | 'positionInRange' returns true if the given 'Position' is in the 'Range'.
93+
positionInRange :: Position -> Range -> Bool
94+
positionInRange p (Range sp ep) = sp <= p && p < ep -- Range's end position is exclusive.

lsp-types/test/LocationSpec.hs

Lines changed: 35 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,35 @@
1+
{-# LANGUAGE OverloadedStrings #-}
2+
3+
module LocationSpec where
4+
5+
import Language.LSP.Types
6+
import Test.Hspec
7+
8+
main :: IO ()
9+
main = hspec spec
10+
11+
spec :: Spec
12+
spec = do
13+
describe "isSubrangeOf" $ do
14+
it "is true if the first range is totally inside the second range" $
15+
isSubrangeOf (mkRange 1 2 1 5) (mkRange 1 1 1 6) `shouldBe` True
16+
it "is true if two ranges equal" $
17+
isSubrangeOf (mkRange 1 2 1 5) (mkRange 1 2 1 5) `shouldBe` True
18+
it "is false if the first range is outside of the second" $
19+
isSubrangeOf (mkRange 1 1 1 5) (mkRange 1 2 1 5) `shouldBe` False
20+
21+
describe "positionInRange" $ do
22+
it "is false if position is after the end of a single line range" $
23+
positionInRange (Position 1 10) (Range (Position 1 1) (Position 1 3)) `shouldBe` False
24+
it "is false if position is before the begining of a single line range" $
25+
positionInRange (Position 1 0) (Range (Position 1 1) (Position 1 6)) `shouldBe` False
26+
it "is true if position is in a single line range" $
27+
positionInRange (Position 1 5) (Range (Position 1 1) (Position 1 6)) `shouldBe` True
28+
it "is false if position is right at the end of the range" $
29+
positionInRange (Position 1 5) (Range (Position 1 1) (Position 1 5)) `shouldBe` False
30+
it "is true if position is in the middle of a multiline range" $
31+
positionInRange (Position 3 5) (Range (Position 1 1) (Position 5 6)) `shouldBe` True
32+
it "is false if position is before the beginning of a multiline range" $
33+
positionInRange (Position 3 5) (Range (Position 3 6) (Position 4 10)) `shouldBe` False
34+
it "is false if position is right at the end of a multiline range" $
35+
positionInRange (Position 4 10) (Range (Position 3 6) (Position 4 10)) `shouldBe` False

0 commit comments

Comments
 (0)