1
1
mirror of https://github.com/github/semantic.git synced 2024-11-26 09:07:39 +03:00

Use newtypes wrappers instead of type synonyms

This commit is contained in:
Timothy Clem 2020-06-29 14:11:04 -07:00
parent 7cc8a87af0
commit 8d3f7368e6
4 changed files with 23 additions and 19 deletions

View File

@ -1,4 +1,4 @@
module Tags.Tag (Tag (..), UTF16CodeUnitSpan, OneIndexedSpan) where
module Tags.Tag (Tag (..), UTF16CodeUnitSpan(..), OneIndexedSpan(..)) where
import Data.Text (Text)
import qualified Proto.Semantic as P
@ -6,10 +6,12 @@ import Source.Loc
-- | A 0-indxed Span where the column offset units are utf-16 code units (2
-- bytes), suitable for the LSP (Language Server Protocol) specification.
type UTF16CodeUnitSpan = Span
newtype UTF16CodeUnitSpan = UTF16CodeUnitSpan { unUTF16CodeUnitSpan :: Span }
deriving (Eq, Show)
-- A 1-indexed Span where the units are bytes.
type OneIndexedSpan = Span
newtype OneIndexedSpan = OneIndexedSpan { unOneIndexedSpan :: Span }
deriving (Eq, Show)
data Tag
= Tag
@ -18,6 +20,6 @@ data Tag
tagNodeType :: P.NodeType,
tagSpan :: OneIndexedSpan,
tagLine :: Text,
tagLspSpan :: UTF16CodeUnitSpan
tagUTF16CodeUnitSpan :: UTF16CodeUnitSpan
}
deriving (Eq, Show)

View File

@ -3,6 +3,8 @@
module Tags.Tagging.Precise
( Tags
, Tag(..)
, OneIndexedSpan(..)
, UTF16CodeUnitSpan(..)
, ToTags(..)
, yield
, runTagging
@ -74,14 +76,14 @@ calculateLineAndSpans
{ start = start@Pos {column = startCol},
end = end@Pos {column = endCol}
}
} =
(line, toOneIndexed span, Span start {column = utf16cpStartOffset} end {column = utf16cpEndOffset})
} = (line, toOneIndexed span, utf16Span)
where
-- NB: Important to limit to 180 characters after converting to text so as not to take in the middle of a multi-byte character.
-- line = Text.strip . Text.take 180 . Source.toText $ srcLine
line = sliceCenter180 startCol . Source.toText $ srcLine
srcLine = surroundingLine src srcRange
toOneIndexed (Span (Pos l1 c1) (Pos l2 c2)) = Span (Pos (l1 + 1) (c1 + 1)) (Pos (l2 + 1) (c2 + 1))
toOneIndexed (Span (Pos l1 c1) (Pos l2 c2)) = OneIndexedSpan $ Span (Pos (l1 + 1) (c1 + 1)) (Pos (l2 + 1) (c2 + 1))
utf16Span = UTF16CodeUnitSpan $ Span start {column = utf16cpStartOffset} end {column = utf16cpEndOffset}
utf16cpStartOffset = countUtf16CodeUnits startSlice
utf16cpEndOffset = utf16cpStartOffset + countUtf16CodeUnits endSlice

View File

@ -23,32 +23,32 @@ testTree = Tasty.testGroup "Tags.Tagging.Precise"
let src = Source.fromText "def foo;end"
loc = Loc (Range 4 7) (Span (Pos 0 4) (Pos 0 7))
in ( "def foo;end"
, Span (Pos 1 5) (Pos 1 8) -- one indexed, counting bytes
, Span (Pos 0 4) (Pos 0 7) -- zero-indexed, counting utf16 code units (lsp-style column offset)
, OneIndexedSpan $ Span (Pos 1 5) (Pos 1 8) -- one indexed, counting bytes
, UTF16CodeUnitSpan $ Span (Pos 0 4) (Pos 0 7) -- zero-indexed, counting utf16 code units (lsp-style column offset)
) @=? calculateLineAndSpans src loc
, testCase "ascii" $
let src = Source.fromText "def foo\n 'a'.hi\nend\n"
loc = Loc (Range 14 16) (Span (Pos 1 6) (Pos 1 8))
in ( "'a'.hi"
, Span (Pos 2 7) (Pos 2 9) -- one indexed, counting bytes
, Span (Pos 1 6) (Pos 1 8) -- zero-indexed, counting utf16 code units (lsp-style column offset)
, OneIndexedSpan $ Span (Pos 2 7) (Pos 2 9) -- one indexed, counting bytes
, UTF16CodeUnitSpan $ Span (Pos 1 6) (Pos 1 8) -- zero-indexed, counting utf16 code units (lsp-style column offset)
) @=? calculateLineAndSpans src loc
, testCase "unicode" $
let src = Source.fromText "def foo\n 'à'.hi\nend\n"
loc = Loc (Range 15 17) (Span (Pos 1 7) (Pos 1 9))
in ( "'à'.hi"
, Span (Pos 2 8) (Pos 2 10) -- one indexed, counting bytes
, Span (Pos 1 6) (Pos 1 8) -- zero-indexed, counting utf16 code units (lsp-style column offset)
, OneIndexedSpan $ Span (Pos 2 8) (Pos 2 10) -- one indexed, counting bytes
, UTF16CodeUnitSpan $ Span (Pos 1 6) (Pos 1 8) -- zero-indexed, counting utf16 code units (lsp-style column offset)
) @=? calculateLineAndSpans src loc
, testCase "multi code point unicode" $
let src = Source.fromText "def foo\n '💀'.hi\nend\n"
loc = Loc (Range 17 19) (Span (Pos 1 9) (Pos 1 11))
in ( "'💀'.hi"
, Span (Pos 2 10) (Pos 2 12) -- one indexed, counting bytes
, Span (Pos 1 7) (Pos 1 9) -- zero-indexed, counting utf16 code units (lsp-style column offset)
, OneIndexedSpan $ Span (Pos 2 10) (Pos 2 12) -- one indexed, counting bytes
, UTF16CodeUnitSpan $ Span (Pos 1 7) (Pos 1 9) -- zero-indexed, counting utf16 code units (lsp-style column offset)
) @=? calculateLineAndSpans src loc
-- NB: This emoji (:man-woman-girl-girl:) cannot be entered into a string literal in haskell for some reason, you'll get:
@ -60,8 +60,8 @@ testTree = Tasty.testGroup "Tags.Tagging.Precise"
let src = Source.fromText "def foo\n '\128104\8205\128105\8205\128103\8205\128103'.hi\nend\n"
loc = Loc (Range 38 40) (Span (Pos 1 30) (Pos 1 32))
in ( "'\128104\8205\128105\8205\128103\8205\128103'.hi"
, Span (Pos 2 31) (Pos 2 33) -- one indexed, counting bytes
, Span (Pos 1 16) (Pos 1 18) -- zero-indexed, counting utf16 code units (lsp-style column offset)
, OneIndexedSpan $ Span (Pos 2 31) (Pos 2 33) -- one indexed, counting bytes
, UTF16CodeUnitSpan $ Span (Pos 1 16) (Pos 1 18) -- zero-indexed, counting utf16 code units (lsp-style column offset)
) @=? calculateLineAndSpans src loc
]
]

View File

@ -76,8 +76,8 @@ parseSymbols blobs = do
& P.nodeType .~ tagNodeType tag
& P.syntaxType .~ tagSyntaxType tag
& P.line .~ tagLine tag
& P.maybe'span ?~ converting # tagSpan tag
& P.maybe'utf16CodeUnitSpan ?~ converting # tagLspSpan tag
& P.maybe'span ?~ converting # unUTF16CodeUnitSpan (tagSpan tag)
& P.maybe'utf16CodeUnitSpan ?~ converting # unOneIndexedSpan (tagLspSpan tag)
where
toKind = toTitle . pack . show . tagSyntaxType