mirror of
https://github.com/github/semantic.git
synced 2024-11-24 08:54:07 +03:00
🔥 rangesAndWordsFrom.
This commit is contained in:
parent
7da94d77f6
commit
ed9b00cc90
@ -148,7 +148,6 @@ test-suite test
|
||||
, SemanticCmdLineSpec
|
||||
, InterpreterSpec
|
||||
, PatchOutputSpec
|
||||
, RangeSpec
|
||||
, SES.Myers.Spec
|
||||
, SourceSpec
|
||||
, SpecHelpers
|
||||
|
@ -1,11 +1,8 @@
|
||||
{-# LANGUAGE DeriveAnyClass #-}
|
||||
module Data.Range where
|
||||
|
||||
import qualified Data.Char as Char
|
||||
import Data.List (span)
|
||||
import Data.List.NonEmpty (nonEmpty)
|
||||
import Data.Semigroup
|
||||
import Data.String
|
||||
import Prologue
|
||||
import Test.LeanCheck
|
||||
|
||||
@ -28,26 +25,6 @@ divideRange :: Range -> Int -> (Range, Range)
|
||||
divideRange Range{..} at = (Range start divider, Range divider end)
|
||||
where divider = max (min end at) start
|
||||
|
||||
-- | Break a string down into words and sequences of punctuation.
|
||||
--
|
||||
-- Returns a list strings with ranges, assuming that the first character in the string is at the given index.
|
||||
rangesAndWordsFrom :: Int -> String -> [(Range, String)]
|
||||
rangesAndWordsFrom _ "" = []
|
||||
rangesAndWordsFrom startIndex string = fromMaybe [] $ take isWord <|> take isPunctuation <|> skip Char.isSpace
|
||||
where
|
||||
save parsed = (Range startIndex $ endFor parsed, parsed)
|
||||
take = parse (Just . save)
|
||||
skip = parse (const Nothing)
|
||||
endFor parsed = startIndex + length parsed
|
||||
parse transform predicate = case span predicate string of
|
||||
([], _) -> Nothing
|
||||
(parsed, rest) -> Just . maybe identity (:) (transform parsed) $ rangesAndWordsFrom (endFor parsed) rest
|
||||
-- Is this a word character?
|
||||
-- Word characters are defined as in [Ruby’s `\p{Word}` syntax](http://ruby-doc.org/core-2.1.1/Regexp.html#class-Regexp-label-Character+Properties), i.e:.
|
||||
-- > A member of one of the following Unicode general category _Letter_, _Mark_, _Number_, _Connector_Punctuation_
|
||||
isWord c = Char.isLetter c || Char.isNumber c || Char.isMark c || Char.generalCategory c == Char.ConnectorPunctuation
|
||||
isPunctuation c = not (Char.isSpace c || isWord c)
|
||||
|
||||
-- | Return Just the last index from a non-empty range, or if the range is empty, Nothing.
|
||||
maybeLastIndex :: Range -> Maybe Int
|
||||
maybeLastIndex (Range start end) | start == end = Nothing
|
||||
|
@ -1,33 +0,0 @@
|
||||
module RangeSpec where
|
||||
|
||||
import Data.Range
|
||||
import Prologue
|
||||
import Test.Hspec (Spec, describe, it, parallel)
|
||||
import Test.Hspec.Expectations.Pretty
|
||||
|
||||
spec :: Spec
|
||||
spec = parallel $ do
|
||||
describe "rangesAndWordsFrom" $ do
|
||||
it "should produce no ranges for the empty string" $
|
||||
rangesAndWordsFrom 0 mempty `shouldBe` []
|
||||
|
||||
it "should produce no ranges for whitespace" $
|
||||
rangesAndWordsFrom 0 " \t\n " `shouldBe` []
|
||||
|
||||
it "should produce a list containing the range of the string for a single-word string" $
|
||||
rangesAndWordsFrom 0 "word" `shouldBe` [ (Range 0 4, "word") ]
|
||||
|
||||
it "should produce a list of ranges for whitespace-separated words" $
|
||||
rangesAndWordsFrom 0 "wordOne wordTwo" `shouldBe` [ (Range 0 7, "wordOne"), (Range 8 15, "wordTwo") ]
|
||||
|
||||
it "should skip multiple whitespace characters" $
|
||||
rangesAndWordsFrom 0 "a b" `shouldBe` [ (Range 0 1, "a"), (Range 3 4, "b") ]
|
||||
|
||||
it "should skip whitespace at the start" $
|
||||
rangesAndWordsFrom 0 " a b" `shouldBe` [ (Range 2 3, "a"), (Range 4 5, "b") ]
|
||||
|
||||
it "should skip whitespace at the end" $
|
||||
rangesAndWordsFrom 0 "a b " `shouldBe` [ (Range 0 1, "a"), (Range 2 3, "b") ]
|
||||
|
||||
it "should produce ranges offset by its start index" $
|
||||
rangesAndWordsFrom 100 "a b" `shouldBe` [ (Range 100 101, "a"), (Range 102 103, "b") ]
|
@ -9,7 +9,6 @@ import qualified Data.Syntax.Assignment.Spec
|
||||
import qualified DiffSpec
|
||||
import qualified InterpreterSpec
|
||||
import qualified PatchOutputSpec
|
||||
import qualified RangeSpec
|
||||
import qualified SES.Myers.Spec
|
||||
import qualified SourceSpec
|
||||
import qualified TermSpec
|
||||
@ -30,7 +29,6 @@ main = hspec $ do
|
||||
describe "Diff" DiffSpec.spec
|
||||
describe "Interpreter" InterpreterSpec.spec
|
||||
describe "PatchOutput" PatchOutputSpec.spec
|
||||
describe "Range" RangeSpec.spec
|
||||
describe "SES.Myers" SES.Myers.Spec.spec
|
||||
describe "Source" SourceSpec.spec
|
||||
describe "Term" TermSpec.spec
|
||||
|
Loading…
Reference in New Issue
Block a user