mirror of
https://github.com/github/semantic.git
synced 2024-11-28 10:15:55 +03:00
Use Text rather than ByteString for Name values.
This commit is contained in:
parent
3641d6d18c
commit
64fd3b0fcc
@ -21,23 +21,23 @@ import Data.Abstract.Name
|
||||
import Data.Abstract.Package (PackageInfo(..))
|
||||
import Data.Aeson hiding (Result)
|
||||
import Data.ByteString.Builder
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.Graph
|
||||
import Data.Sum
|
||||
import qualified Data.Syntax as Syntax
|
||||
import Data.Term
|
||||
import Data.Text.Encoding as T
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as T
|
||||
import Prologue hiding (packageName, project)
|
||||
|
||||
-- | A vertex of some specific type.
|
||||
data Vertex
|
||||
= Package { vertexName :: ByteString }
|
||||
| Module { vertexName :: ByteString }
|
||||
| Variable { vertexName :: ByteString }
|
||||
= Package { vertexName :: Text }
|
||||
| Module { vertexName :: Text }
|
||||
| Variable { vertexName :: Text }
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
style :: Style Vertex Builder
|
||||
style = (defaultStyle (byteString . vertexName))
|
||||
style = (defaultStyle (T.encodeUtf8Builder . vertexName))
|
||||
{ vertexAttributes = vertexAttributes
|
||||
, edgeAttributes = edgeAttributes
|
||||
}
|
||||
@ -96,7 +96,7 @@ packageVertex :: PackageInfo -> Vertex
|
||||
packageVertex = Package . unName . packageName
|
||||
|
||||
moduleVertex :: ModuleInfo -> Vertex
|
||||
moduleVertex = Module . BC.pack . modulePath
|
||||
moduleVertex = Module . T.pack . modulePath
|
||||
|
||||
-- | Add an edge from the current package to the passed vertex.
|
||||
packageInclusion :: ( Effectful m
|
||||
@ -143,7 +143,7 @@ instance ToJSON Vertex where
|
||||
toJSON v = object [ "name" .= vertexToText v, "type" .= vertexToType v ]
|
||||
|
||||
vertexToText :: Vertex -> Text
|
||||
vertexToText = decodeUtf8 . vertexName
|
||||
vertexToText = vertexName
|
||||
|
||||
vertexToType :: Vertex -> Text
|
||||
vertexToType Package{} = "package"
|
||||
|
@ -19,7 +19,6 @@ import qualified Data.Syntax.Declaration as Declaration
|
||||
import qualified Data.Syntax.Expression as Expression
|
||||
import Data.Term
|
||||
import qualified Data.Text as T
|
||||
import qualified Data.Text.Encoding as T
|
||||
import qualified Language.Markdown.Syntax as Markdown
|
||||
import qualified Language.Ruby.Syntax as Ruby.Syntax
|
||||
import Prologue hiding (project)
|
||||
@ -130,7 +129,7 @@ getSource blobSource = toText . flip Source.slice blobSource . getField
|
||||
instance (Syntax.Identifier :< fs, Expression.MemberAccess :< fs) => CustomHasDeclaration (Sum fs) Expression.Call where
|
||||
customToDeclaration Blob{..} _ (Expression.Call _ (Term (In fromAnn fromF), _) _ _)
|
||||
| Just (Expression.MemberAccess (Term (In leftAnn leftF)) (Term (In idenAnn _))) <- project fromF = Just $ CallReference (getSource idenAnn) mempty blobLanguage (memberAccess leftAnn leftF)
|
||||
| Just (Syntax.Identifier name) <- project fromF = Just $ CallReference (T.decodeUtf8 (unName name)) mempty blobLanguage []
|
||||
| Just (Syntax.Identifier name) <- project fromF = Just $ CallReference (unName name) mempty blobLanguage []
|
||||
| otherwise = Just $ CallReference (getSource fromAnn) mempty blobLanguage []
|
||||
where
|
||||
memberAccess modAnn termFOut
|
||||
|
@ -11,31 +11,30 @@ import Data.JSON.Fields
|
||||
import Data.Sum
|
||||
import qualified Data.Syntax
|
||||
import Data.Term
|
||||
import Data.Text.Encoding (decodeUtf8)
|
||||
import Prologue
|
||||
|
||||
-- | Compute a 'IdentifierLabel' label for a 'Term'.
|
||||
identifierLabel :: IdentifierName syntax => TermF syntax a b -> Maybe IdentifierLabel
|
||||
identifierLabel (In _ s) = IdentifierLabel <$> identifierName s
|
||||
|
||||
newtype IdentifierLabel = IdentifierLabel ByteString
|
||||
newtype IdentifierLabel = IdentifierLabel Text
|
||||
deriving (Show)
|
||||
|
||||
instance ToJSONFields IdentifierLabel where
|
||||
toJSONFields (IdentifierLabel s) = [ "name" .= decodeUtf8 s ]
|
||||
toJSONFields (IdentifierLabel s) = [ "name" .= s ]
|
||||
|
||||
|
||||
-- | A typeclass to retrieve the name of syntax identifiers.
|
||||
--
|
||||
-- This typeclass employs the Advanced Overlap techniques designed by Oleg Kiselyov & Simon Peyton Jones: https://wiki.haskell.org/GHC/AdvancedOverlap; see also src/Analysis/Declaration.hs for discussion of the details of the mechanism.
|
||||
class IdentifierName syntax where
|
||||
identifierName :: syntax a -> Maybe ByteString
|
||||
identifierName :: syntax a -> Maybe Text
|
||||
|
||||
instance (IdentifierNameStrategy syntax ~ strategy, IdentifierNameWithStrategy strategy syntax) => IdentifierName syntax where
|
||||
identifierName = identifierNameWithStrategy (Proxy :: Proxy strategy)
|
||||
|
||||
class CustomIdentifierName syntax where
|
||||
customIdentifierName :: syntax a -> Maybe ByteString
|
||||
customIdentifierName :: syntax a -> Maybe Text
|
||||
|
||||
instance Apply IdentifierName fs => CustomIdentifierName (Sum fs) where
|
||||
customIdentifierName = apply @IdentifierName identifierName
|
||||
@ -51,7 +50,7 @@ type family IdentifierNameStrategy syntax where
|
||||
IdentifierNameStrategy syntax = 'Default
|
||||
|
||||
class IdentifierNameWithStrategy (strategy :: Strategy) syntax where
|
||||
identifierNameWithStrategy :: proxy strategy -> syntax a -> Maybe ByteString
|
||||
identifierNameWithStrategy :: proxy strategy -> syntax a -> Maybe Text
|
||||
|
||||
instance IdentifierNameWithStrategy 'Default syntax where
|
||||
identifierNameWithStrategy _ _ = Nothing
|
||||
|
@ -70,6 +70,7 @@ module Assigning.Assignment
|
||||
, currentNode
|
||||
, symbol
|
||||
, source
|
||||
, tsource
|
||||
, children
|
||||
, advance
|
||||
, choice
|
||||
@ -104,6 +105,8 @@ import Data.Record
|
||||
import qualified Data.Source as Source (Source, slice, sourceBytes)
|
||||
import Data.Span
|
||||
import Data.Term
|
||||
import Data.Text (Text)
|
||||
import Data.Text.Encoding (decodeUtf8')
|
||||
import Text.Parser.Combinators as Parsers hiding (choice)
|
||||
import TreeSitter.Language
|
||||
|
||||
@ -123,8 +126,8 @@ data AssignmentF ast grammar a where
|
||||
Alt :: [a] -> AssignmentF ast grammar a
|
||||
Label :: Assignment ast grammar a -> String -> AssignmentF ast grammar a
|
||||
Fail :: String -> AssignmentF ast grammar a
|
||||
GetRubyLocals :: AssignmentF ast grammar [ByteString]
|
||||
PutRubyLocals :: [ByteString] -> AssignmentF ast grammar ()
|
||||
GetRubyLocals :: AssignmentF ast grammar [Text]
|
||||
PutRubyLocals :: [Text] -> AssignmentF ast grammar ()
|
||||
|
||||
data Tracing f a where
|
||||
Tracing :: { tracingCallSite :: Maybe (String, SrcLoc), runTracing :: f a } -> Tracing f a
|
||||
@ -144,10 +147,10 @@ tracing f = case getCallStack callStack of
|
||||
location :: HasCallStack => Assignment ast grammar (Record Location)
|
||||
location = tracing Location `Then` return
|
||||
|
||||
getRubyLocals :: HasCallStack => Assignment ast grammar [ByteString]
|
||||
getRubyLocals :: HasCallStack => Assignment ast grammar [Text]
|
||||
getRubyLocals = tracing GetRubyLocals `Then` return
|
||||
|
||||
putRubyLocals :: (HasCallStack, Enum grammar, Eq1 ast, Ix grammar) => [ByteString] -> Assignment ast grammar ()
|
||||
putRubyLocals :: (HasCallStack, Enum grammar, Eq1 ast, Ix grammar) => [Text] -> Assignment ast grammar ()
|
||||
putRubyLocals l = (tracing (PutRubyLocals l) `Then` return)
|
||||
<|> (tracing End `Then` return)
|
||||
|
||||
@ -160,9 +163,15 @@ symbol :: (Enum grammar, Ix grammar, HasCallStack) => grammar -> Assignment ast
|
||||
symbol s = tracing (Choose (Table.singleton s location) Nothing Nothing) `Then` return
|
||||
|
||||
-- | A rule to produce a node’s source as a ByteString.
|
||||
-- Deprecated: please use source'.
|
||||
source :: HasCallStack => Assignment ast grammar ByteString
|
||||
source = tracing Source `Then` return
|
||||
|
||||
tsource :: HasCallStack => Assignment ast grammar Text
|
||||
tsource = source >>= \b -> case decodeUtf8' b of
|
||||
Right t -> pure t
|
||||
Left e -> fail ("UTF-8 decoding failed: " <> show e)
|
||||
|
||||
-- | Match a node by applying an assignment to its children.
|
||||
children :: HasCallStack => Assignment ast grammar a -> Assignment ast grammar a
|
||||
children child = tracing (Children child) `Then` return
|
||||
@ -299,7 +308,7 @@ data State ast grammar = State
|
||||
, statePos :: {-# UNPACK #-} !Pos -- ^ The (1-indexed) line/column position in the Source thus far reached.
|
||||
, stateCallSites :: ![(String, SrcLoc)] -- ^ The symbols & source locations of the calls thus far.
|
||||
, stateNodes :: ![AST ast grammar] -- ^ The remaining nodes to assign. Note that 'children' rules recur into subterms, and thus this does not necessarily reflect all of the terms remaining to be assigned in the overall algorithm, only those “in scope.”
|
||||
, stateRubyLocals :: ![ByteString] -- Special state necessary for the Ruby assignment. When we refactor Assignment to use effects we should pull this out into Language.Ruby.Assignment
|
||||
, stateRubyLocals :: ![Text] -- Special state necessary for the Ruby assignment. When we refactor Assignment to use effects we should pull this out into Language.Ruby.Assignment
|
||||
}
|
||||
|
||||
deriving instance (Eq grammar, Eq1 ast) => Eq (State ast grammar)
|
||||
|
@ -1,5 +1,7 @@
|
||||
module Control.Abstract.Primitive where
|
||||
|
||||
import Prologue
|
||||
|
||||
import Control.Abstract.Addressable
|
||||
import Control.Abstract.Context
|
||||
import Control.Abstract.Environment
|
||||
@ -8,10 +10,10 @@ import Control.Abstract.Heap
|
||||
import Control.Abstract.Value
|
||||
import Data.Abstract.Environment
|
||||
import Data.Abstract.Name
|
||||
import Data.ByteString.Char8 (pack, unpack)
|
||||
import Data.Semigroup.Reducer hiding (unit)
|
||||
import Data.Semilattice.Lower
|
||||
import Prologue
|
||||
import qualified Data.ByteString.Char8 as B
|
||||
import qualified Data.Text as T
|
||||
|
||||
builtin :: ( HasCallStack
|
||||
, Members '[ Allocator location value
|
||||
@ -28,7 +30,7 @@ builtin :: ( HasCallStack
|
||||
-> Evaluator location value effects value
|
||||
-> Evaluator location value effects ()
|
||||
builtin n def = withCurrentCallStack callStack $ do
|
||||
let name' = name ("__semantic_" <> pack n)
|
||||
let name' = name ("__semantic_" <> T.pack n)
|
||||
addr <- alloc name'
|
||||
modifyEnv (insert name' addr)
|
||||
def >>= assign addr
|
||||
@ -58,4 +60,4 @@ defineBuiltins :: ( AbstractValue location value effects
|
||||
)
|
||||
=> Evaluator location value effects ()
|
||||
defineBuiltins =
|
||||
builtin "print" (lambda lowerBound (\ v -> variable v >>= asString >>= trace . unpack >> unit))
|
||||
builtin "print" (lambda lowerBound (\ v -> variable v >>= asString >>= trace . B.unpack >> unit))
|
||||
|
@ -121,7 +121,7 @@ class AbstractFunction location value effects => AbstractValue location value ef
|
||||
-- | Construct a hash out of pairs.
|
||||
hash :: [(value, value)] -> Evaluator location value effects value
|
||||
|
||||
-- | Extract a 'ByteString' from a given value.
|
||||
-- | Extract a 'Text' from a given value.
|
||||
asString :: value -> Evaluator location value effects ByteString
|
||||
|
||||
-- | Eliminate boolean values. TODO: s/boolean/truthy
|
||||
|
@ -6,36 +6,35 @@ module Data.Abstract.Name
|
||||
, unName
|
||||
) where
|
||||
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import qualified Data.Char as Char
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as Text
|
||||
import qualified Data.Text.Encoding as Text
|
||||
import Data.String
|
||||
import Prologue
|
||||
|
||||
-- | The type of variable names.
|
||||
data Name
|
||||
= Name ByteString
|
||||
= Name Text
|
||||
| I Int
|
||||
deriving (Eq, Ord)
|
||||
|
||||
-- | Construct a 'Name' from a 'ByteString'.
|
||||
name :: ByteString -> Name
|
||||
name :: Text -> Name
|
||||
name = Name
|
||||
|
||||
-- | Construct a 'Name' from an 'Int'. This is suitable for automatic generation, e.g. using a Fresh effect, but should not be used for human-generated names.
|
||||
nameI :: Int -> Name
|
||||
nameI = I
|
||||
|
||||
-- | Extract a human-readable 'ByteString' from a 'Name'.
|
||||
unName :: Name -> ByteString
|
||||
-- | Extract a human-readable 'Text' from a 'Name'.
|
||||
unName :: Name -> Text
|
||||
unName (Name name) = name
|
||||
unName (I i) = Text.encodeUtf8 . Text.pack $ '_' : (alphabet !! a) : replicate n 'ʹ'
|
||||
unName (I i) = Text.pack $ '_' : (alphabet !! a) : replicate n 'ʹ'
|
||||
where alphabet = ['a'..'z']
|
||||
(n, a) = i `divMod` length alphabet
|
||||
|
||||
instance IsString Name where
|
||||
fromString = Name . BC.pack
|
||||
fromString = Name . Text.pack
|
||||
|
||||
-- $
|
||||
-- >>> I 0
|
||||
@ -43,7 +42,7 @@ instance IsString Name where
|
||||
-- >>> I 26
|
||||
-- "_aʹ"
|
||||
instance Show Name where
|
||||
showsPrec _ = prettyShowString . Text.unpack . Text.decodeUtf8 . unName
|
||||
showsPrec _ = prettyShowString . Text.unpack . unName
|
||||
where prettyShowString str = showChar '"' . foldr ((.) . prettyChar) id str . showChar '"'
|
||||
prettyChar c
|
||||
| c `elem` ['\\', '\"'] = Char.showLitChar c
|
||||
|
@ -1,6 +1,6 @@
|
||||
module Data.Project where
|
||||
|
||||
import Data.ByteString.Char8 as BC (pack)
|
||||
import Data.Text as T (pack)
|
||||
import Data.Language
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
@ -14,8 +14,8 @@ data Project = Project
|
||||
}
|
||||
deriving (Eq, Ord, Show)
|
||||
|
||||
projectName :: Project -> ByteString
|
||||
projectName = BC.pack . dropExtensions . takeFileName . projectRootDir
|
||||
projectName :: Project -> Text
|
||||
projectName = T.pack . dropExtensions . takeFileName . projectRootDir
|
||||
|
||||
projectExtensions :: Project -> [String]
|
||||
projectExtensions = extensionsForLanguage . projectLanguage
|
||||
|
@ -225,13 +225,13 @@ element :: Assignment
|
||||
element = symbol Element *> children expression
|
||||
|
||||
fieldIdentifier :: Assignment
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier . name <$> source)
|
||||
fieldIdentifier = makeTerm <$> symbol FieldIdentifier <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
floatLiteral :: Assignment
|
||||
floatLiteral = makeTerm <$> symbol FloatLiteral <*> (Literal.Float <$> source)
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier . name <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
imaginaryLiteral :: Assignment
|
||||
imaginaryLiteral = makeTerm <$> symbol ImaginaryLiteral <*> (Literal.Complex <$> source)
|
||||
@ -246,7 +246,7 @@ literalValue :: Assignment
|
||||
literalValue = makeTerm <$> symbol LiteralValue <*> children (manyTerm expression)
|
||||
|
||||
packageIdentifier :: Assignment
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier . name <$> source)
|
||||
packageIdentifier = makeTerm <$> symbol PackageIdentifier <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
parenthesizedType :: Assignment
|
||||
parenthesizedType = makeTerm <$> symbol Grammar.ParenthesizedType <*> children (Type.Parenthesized <$> expression)
|
||||
@ -258,7 +258,7 @@ runeLiteral :: Assignment
|
||||
runeLiteral = makeTerm <$> symbol Grammar.RuneLiteral <*> (Go.Syntax.Rune <$> source)
|
||||
|
||||
typeIdentifier :: Assignment
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier . name <$> source)
|
||||
typeIdentifier = makeTerm <$> symbol TypeIdentifier <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
|
||||
-- Primitive Types
|
||||
@ -373,7 +373,7 @@ expressionSwitchStatement :: Assignment
|
||||
expressionSwitchStatement = makeTerm <$> symbol ExpressionSwitchStatement <*> children (Statement.Match <$> (makeTerm <$> location <*> manyTermsTill expression (void (symbol ExpressionCaseClause)) <|> emptyTerm) <*> expressions)
|
||||
|
||||
fallThroughStatement :: Assignment
|
||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> emptyTerm)
|
||||
fallThroughStatement = makeTerm <$> symbol FallthroughStatement <*> (Statement.Pattern <$> (makeTerm <$> location <*> (Syntax.Identifier . name <$> tsource)) <*> emptyTerm)
|
||||
|
||||
functionDeclaration :: Assignment
|
||||
functionDeclaration = makeTerm <$> (symbol FunctionDeclaration <|> symbol FuncLiteral) <*> children (mkFunctionDeclaration <$> (term identifier <|> emptyTerm) <*> manyTerm parameters <*> (term types <|> term identifier <|> term returnParameters <|> emptyTerm) <*> (term block <|> emptyTerm))
|
||||
@ -392,7 +392,7 @@ importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTe
|
||||
namedImport = inject <$> (flip Go.Syntax.QualifiedImport <$> packageIdentifier <*> importFromPath)
|
||||
-- `import "lib/Math"`
|
||||
plainImport = inject <$> (symbol InterpretedStringLiteral >>= \loc -> do
|
||||
from <- importPath <$> source
|
||||
from <- importPath <$> tsource
|
||||
let alias = makeTerm loc (Syntax.Identifier (defaultAlias from)) -- Go takes `import "lib/Math"` and uses `Math` as the qualified name (e.g. `Math.Sin()`)
|
||||
Go.Syntax.QualifiedImport <$> pure from <*> pure alias)
|
||||
|
||||
@ -400,7 +400,7 @@ importDeclaration = makeTerm'' <$> symbol ImportDeclaration <*> children (manyTe
|
||||
underscore = makeTerm <$> symbol BlankIdentifier <*> (Literal.TextElement <$> source)
|
||||
importSpec = makeTerm' <$> symbol ImportSpec <*> children (sideEffectImport <|> dotImport <|> namedImport <|> plainImport)
|
||||
importSpecList = makeTerm <$> symbol ImportSpecList <*> children (manyTerm (importSpec <|> comment))
|
||||
importFromPath = symbol InterpretedStringLiteral *> (importPath <$> source)
|
||||
importFromPath = symbol InterpretedStringLiteral *> (importPath <$> tsource)
|
||||
|
||||
indexExpression :: Assignment
|
||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
||||
@ -564,7 +564,7 @@ keyedElement :: Assignment
|
||||
keyedElement = makeTerm <$> symbol KeyedElement <*> children (Literal.KeyValue <$> expression <*> expression)
|
||||
|
||||
labelName :: Assignment
|
||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier . name <$> source)
|
||||
labelName = makeTerm <$> symbol LabelName <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
labeledStatement :: Assignment
|
||||
labeledStatement = makeTerm <$> (symbol LabeledStatement <|> symbol LabeledStatement') <*> children (Go.Syntax.Label <$> expression <*> (expression <|> emptyTerm))
|
||||
|
@ -5,9 +5,8 @@ import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module
|
||||
import qualified Data.Abstract.Package as Package
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Text as T
|
||||
import Diffing.Algorithm
|
||||
import Prologue
|
||||
import System.FilePath.Posix
|
||||
@ -18,15 +17,15 @@ data Relative = Relative | NonRelative
|
||||
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show)
|
||||
|
||||
importPath :: ByteString -> ImportPath
|
||||
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path)
|
||||
importPath :: Text -> ImportPath
|
||||
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
|
||||
where
|
||||
stripQuotes = B.filter (`B.notElem` "\'\"")
|
||||
pathType xs | not (B.null xs), BC.head xs == '.' = Relative
|
||||
stripQuotes = T.dropAround (`elem` ("\'\"" :: String))
|
||||
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- TODO: head is partial
|
||||
| otherwise = NonRelative
|
||||
|
||||
defaultAlias :: ImportPath -> Name
|
||||
defaultAlias = name . BC.pack . takeFileName . unPath
|
||||
defaultAlias = name . T.pack . takeFileName . unPath
|
||||
|
||||
resolveGoImport :: Members '[ Modules location value
|
||||
, Reader ModuleInfo
|
||||
@ -43,7 +42,7 @@ resolveGoImport (ImportPath path Relative) = do
|
||||
[] -> throwResumable $ GoImportError path
|
||||
_ -> pure paths
|
||||
resolveGoImport (ImportPath path NonRelative) = do
|
||||
package <- BC.unpack . unName . Package.packageName <$> currentPackage
|
||||
package <- T.unpack . unName . Package.packageName <$> currentPackage
|
||||
trace ("attempting to resolve " <> show path <> " for package " <> package)
|
||||
case splitDirectories path of
|
||||
-- Import an absolute path that's defined in this package being analyzed.
|
||||
|
@ -72,13 +72,13 @@ comment :: Assignment
|
||||
comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
variableIdentifier :: Assignment
|
||||
variableIdentifier = makeTerm <$> symbol VariableIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
variableIdentifier = makeTerm <$> symbol VariableIdentifier <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
constructorIdentifier :: Assignment
|
||||
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
constructorIdentifier = makeTerm <$> symbol ConstructorIdentifier <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
moduleIdentifier :: Assignment
|
||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
moduleIdentifier = makeTerm <$> symbol ModuleIdentifier <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
where' :: Assignment
|
||||
where' = makeTerm <$> (symbol Where <|> symbol Where') <*> children (many expression)
|
||||
|
@ -445,7 +445,7 @@ classConstDeclaration :: Assignment
|
||||
classConstDeclaration = makeTerm <$> symbol ClassConstDeclaration <*> children (Syntax.ClassConstDeclaration <$> (term visibilityModifier <|> emptyTerm) <*> manyTerm constElement)
|
||||
|
||||
visibilityModifier :: Assignment
|
||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier . Name.name <$> source)
|
||||
visibilityModifier = makeTerm <$> symbol VisibilityModifier <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
constElement :: Assignment
|
||||
constElement = makeTerm <$> symbol ConstElement <*> children (Statement.Assignment [] <$> term name <*> term expression)
|
||||
@ -651,7 +651,7 @@ propertyDeclaration :: Assignment
|
||||
propertyDeclaration = makeTerm <$> symbol PropertyDeclaration <*> children (Syntax.PropertyDeclaration <$> term propertyModifier <*> someTerm propertyElement)
|
||||
|
||||
propertyModifier :: Assignment
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier . Name.name <$> source))
|
||||
propertyModifier = (makeTerm <$> symbol PropertyModifier <*> children (Syntax.PropertyModifier <$> (term visibilityModifier <|> emptyTerm) <*> (term staticModifier <|> emptyTerm))) <|> term (makeTerm <$> symbol PropertyModifier <*> (Syntax.Identifier . Name.name <$> tsource))
|
||||
|
||||
propertyElement :: Assignment
|
||||
propertyElement = makeTerm <$> symbol PropertyElement <*> children (Statement.Assignment [] <$> term variableName <*> term propertyInitializer) <|> (symbol PropertyElement *> children (term variableName))
|
||||
@ -712,7 +712,7 @@ namespaceAliasingClause = makeTerm <$> symbol NamespaceAliasingClause <*> childr
|
||||
|
||||
-- | TODO Do something better than Identifier
|
||||
namespaceFunctionOrConst :: Assignment
|
||||
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier . Name.name <$> source)
|
||||
namespaceFunctionOrConst = makeTerm <$> symbol NamespaceFunctionOrConst <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
globalDeclaration :: Assignment
|
||||
globalDeclaration = makeTerm <$> symbol GlobalDeclaration <*> children (Syntax.GlobalDeclaration <$> manyTerm simpleVariable')
|
||||
@ -748,7 +748,7 @@ variableName :: Assignment
|
||||
variableName = makeTerm <$> symbol VariableName <*> children (Syntax.VariableName <$> term name)
|
||||
|
||||
name :: Assignment
|
||||
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier . Name.name <$> source)
|
||||
name = makeTerm <$> (symbol Name <|> symbol Name') <*> (Syntax.Identifier . Name.name <$> tsource)
|
||||
|
||||
functionStaticDeclaration :: Assignment
|
||||
functionStaticDeclaration = makeTerm <$> symbol FunctionStaticDeclaration <*> children (Declaration.VariableDeclaration <$> manyTerm staticVariableDeclaration)
|
||||
|
@ -182,10 +182,10 @@ expressionList :: Assignment
|
||||
expressionList = makeTerm'' <$> symbol ExpressionList <*> children (someTerm expression)
|
||||
|
||||
listSplat :: Assignment
|
||||
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier . name <$> source)
|
||||
listSplat = makeTerm <$> symbol ListSplat <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
dictionarySplat :: Assignment
|
||||
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier . name <$> source)
|
||||
dictionarySplat = makeTerm <$> symbol DictionarySplat <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
keywordArgument :: Assignment
|
||||
keywordArgument = makeTerm <$> symbol KeywordArgument <*> children (Statement.Assignment [] <$> term expression <*> term expression)
|
||||
@ -339,7 +339,7 @@ yield :: Assignment
|
||||
yield = makeTerm <$> symbol Yield <*> (Statement.Yield <$> children (term ( expression <|> emptyTerm )))
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier' <|> symbol DottedName) <*> (Syntax.Identifier . name <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier' <|> symbol DottedName) <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
set :: Assignment
|
||||
set = makeTerm <$> symbol Set <*> children (Literal.Set <$> manyTerm expression)
|
||||
@ -381,20 +381,20 @@ import' = makeTerm'' <$> symbol ImportStatement <*> children (manyTerm (aliase
|
||||
-- `from a import foo as bar`
|
||||
aliasImportSymbol = symbol AliasedImport *> children (makeNameAliasPair <$> aliasIdentifier <*> (Just <$> aliasIdentifier))
|
||||
-- `from a import *`
|
||||
wildcard = symbol WildcardImport *> (name <$> source) $> []
|
||||
wildcard = symbol WildcardImport *> (name <$> tsource) $> []
|
||||
|
||||
importPath = importDottedName <|> importRelative
|
||||
importDottedName = symbol DottedName *> children (qualifiedName <$> NonEmpty.some1 identifierSource)
|
||||
importRelative = symbol RelativeImport *> children (relativeQualifiedName <$> importPrefix <*> ((symbol DottedName *> children (many identifierSource)) <|> pure []))
|
||||
importPrefix = symbol ImportPrefix *> source
|
||||
identifierSource = (symbol Identifier <|> symbol Identifier') *> source
|
||||
importPrefix = symbol ImportPrefix *> tsource
|
||||
identifierSource = (symbol Identifier <|> symbol Identifier') *> tsource
|
||||
|
||||
aliasIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source) <|> symbol DottedName *> (name <$> source)
|
||||
aliasIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> tsource) <|> symbol DottedName *> (name <$> tsource)
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
|
||||
assertStatement :: Assignment
|
||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
assertStatement = makeTerm <$> symbol AssertStatement <*> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonAssert <*> (Syntax.Identifier . name <$> tsource)) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
printStatement :: Assignment
|
||||
printStatement = do
|
||||
@ -403,25 +403,25 @@ printStatement = do
|
||||
print <- term printKeyword
|
||||
term (redirectCallTerm location print <|> printCallTerm location print)
|
||||
where
|
||||
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier . name <$> source)
|
||||
printKeyword = makeTerm <$> symbol AnonPrint <*> (Syntax.Identifier . name <$> tsource)
|
||||
redirectCallTerm location identifier = makeTerm location <$ symbol Chevron <*> (flip Python.Syntax.Redirect <$> children (term expression) <*> term (printCallTerm location identifier))
|
||||
printCallTerm location identifier = makeTerm location <$> (Expression.Call [] identifier <$> manyTerm expression <*> emptyTerm)
|
||||
|
||||
nonlocalStatement :: Assignment
|
||||
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
nonlocalStatement = makeTerm <$> symbol NonlocalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonNonlocal <*> (Syntax.Identifier . name <$> tsource)) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
globalStatement :: Assignment
|
||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
globalStatement = makeTerm <$> symbol GlobalStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonGlobal <*> (Syntax.Identifier . name <$> tsource)) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
await :: Assignment
|
||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> source)) <*> manyTerm expression <*> emptyTerm)
|
||||
await = makeTerm <$> symbol Await <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> symbol AnonAwait <*> (Syntax.Identifier . name <$> tsource)) <*> manyTerm expression <*> emptyTerm)
|
||||
|
||||
returnStatement :: Assignment
|
||||
returnStatement = makeTerm <$> symbol ReturnStatement <*> children (Statement.Return <$> term (expressionList <|> emptyTerm))
|
||||
|
||||
deleteStatement :: Assignment
|
||||
deleteStatement = makeTerm <$> symbol DeleteStatement <*> children (Expression.Call <$> pure [] <*> term deleteIdentifier <* symbol ExpressionList <*> children (manyTerm expression) <*> emptyTerm)
|
||||
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier . name <$> source)
|
||||
where deleteIdentifier = makeTerm <$> symbol AnonDel <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
raiseStatement :: Assignment
|
||||
raiseStatement = makeTerm <$> symbol RaiseStatement <*> children (Statement.Throw <$> expressions)
|
||||
@ -432,7 +432,7 @@ ifStatement = makeTerm <$> symbol IfStatement <*> children (Statement.If <$> ter
|
||||
makeElif (loc, makeIf) rest = makeTerm loc (makeIf rest)
|
||||
|
||||
execStatement :: Assignment
|
||||
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> source)) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
||||
execStatement = makeTerm <$> symbol ExecStatement <*> children (Expression.Call <$> pure [] <*> term (makeTerm <$> location <*> (Syntax.Identifier . name <$> tsource)) <*> manyTerm (string <|> expression) <*> emptyTerm)
|
||||
|
||||
passStatement :: Assignment
|
||||
passStatement = makeTerm <$> symbol PassStatement <*> (Statement.NoOp <$> emptyTerm <* advance)
|
||||
|
@ -5,13 +5,13 @@ import Data.Abstract.Environment as Env
|
||||
import Data.Abstract.Evaluatable
|
||||
import Data.Abstract.Module
|
||||
import Data.Align.Generic
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import Data.Functor.Classes.Generic
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.List.NonEmpty as NonEmpty
|
||||
import qualified Data.Semigroup.Reducer as Reducer
|
||||
import Data.Mergeable
|
||||
import qualified Data.Semigroup.Reducer as Reducer
|
||||
import qualified Data.Text as T
|
||||
import Diffing.Algorithm
|
||||
import GHC.Generics
|
||||
import Prelude hiding (fail)
|
||||
@ -23,12 +23,12 @@ data QualifiedName
|
||||
| RelativeQualifiedName FilePath (Maybe QualifiedName)
|
||||
deriving (Eq, Generic, Hashable, Ord, Show)
|
||||
|
||||
qualifiedName :: NonEmpty ByteString -> QualifiedName
|
||||
qualifiedName xs = QualifiedName (BC.unpack <$> xs)
|
||||
qualifiedName :: NonEmpty Text -> QualifiedName
|
||||
qualifiedName xs = QualifiedName (T.unpack <$> xs)
|
||||
|
||||
relativeQualifiedName :: ByteString -> [ByteString] -> QualifiedName
|
||||
relativeQualifiedName prefix [] = RelativeQualifiedName (BC.unpack prefix) Nothing
|
||||
relativeQualifiedName prefix paths = RelativeQualifiedName (BC.unpack prefix) (Just (qualifiedName (NonEmpty.fromList paths)))
|
||||
relativeQualifiedName :: Text -> [Text] -> QualifiedName
|
||||
relativeQualifiedName prefix [] = RelativeQualifiedName (T.unpack prefix) Nothing
|
||||
relativeQualifiedName prefix paths = RelativeQualifiedName (T.unpack prefix) (Just (qualifiedName (NonEmpty.fromList paths)))
|
||||
|
||||
-- Python module resolution.
|
||||
-- https://docs.python.org/3/reference/import.html#importsystem
|
||||
@ -159,7 +159,7 @@ instance Evaluatable QualifiedImport where
|
||||
eval (QualifiedImport (RelativeQualifiedName _ _)) = raiseEff (fail "technically this is not allowed in python")
|
||||
eval (QualifiedImport qname@(QualifiedName qualifiedName)) = do
|
||||
modulePaths <- resolvePythonModules qname
|
||||
Rval <$> go (NonEmpty.zip (name . BC.pack <$> qualifiedName) modulePaths)
|
||||
Rval <$> go (NonEmpty.zip (name . T.pack <$> qualifiedName) modulePaths)
|
||||
where
|
||||
-- Evaluate and import the last module, updating the environment
|
||||
go ((name, path) :| []) = evalQualifiedImport name path
|
||||
|
@ -178,7 +178,7 @@ identifier =
|
||||
<|> mk BlockArgument
|
||||
<|> mk Uninterpreted
|
||||
where
|
||||
mk s = makeTerm <$> symbol s <*> (Syntax.Identifier . name <$> source)
|
||||
mk s = makeTerm <$> symbol s <*> (Syntax.Identifier . name <$> tsource)
|
||||
vcallOrLocal = do
|
||||
(loc, ident, locals) <- identWithLocals
|
||||
case ident of
|
||||
@ -286,11 +286,11 @@ comment = makeTerm <$> symbol Comment <*> (Comment.Comment <$> source)
|
||||
|
||||
alias :: Assignment
|
||||
alias = makeTerm <$> symbol Alias <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier . name <$> source)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
undef :: Assignment
|
||||
undef = makeTerm <$> symbol Undef <*> children (Expression.Call <$> pure [] <*> name' <*> some expression <*> emptyTerm)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier . name <$> source)
|
||||
where name' = makeTerm <$> location <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
if' :: Assignment
|
||||
if' = ifElsif If
|
||||
@ -361,7 +361,7 @@ methodCall = makeTerm' <$> symbol MethodCall <*> children (require <|> load <|>
|
||||
nameExpression = (symbol ArgumentList <|> symbol ArgumentListWithParens) *> children expression
|
||||
|
||||
methodSelector :: Assignment
|
||||
methodSelector = makeTerm <$> symbols <*> (Syntax.Identifier <$> (name <$> source))
|
||||
methodSelector = makeTerm <$> symbols <*> (Syntax.Identifier <$> (name <$> tsource))
|
||||
where
|
||||
symbols = symbol Identifier
|
||||
<|> symbol Constant
|
||||
@ -411,17 +411,17 @@ assignment' = makeTerm <$> symbol Assignment <*> children (Statement.As
|
||||
|
||||
lhs = makeTerm <$> symbol LeftAssignmentList <*> children (many expr) <|> expr
|
||||
rhs = makeTerm <$> symbol RightAssignmentList <*> children (many expr) <|> expr
|
||||
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier . name <$> source)
|
||||
expr = makeTerm <$> symbol RestAssignment <*> (Syntax.Identifier . name <$> tsource)
|
||||
<|> makeTerm <$> symbol DestructuredLeftAssignment <*> children (many expr)
|
||||
<|> lhsIdent
|
||||
<|> expression
|
||||
|
||||
identWithLocals :: Assignment' (Record Location, ByteString, [ByteString])
|
||||
identWithLocals :: Assignment' (Record Location, Text, [Text])
|
||||
identWithLocals = do
|
||||
loc <- symbol Identifier
|
||||
-- source advances, so it's important we call getRubyLocals first
|
||||
locals <- getRubyLocals
|
||||
ident <- source
|
||||
ident <- tsource
|
||||
pure (loc, ident, locals)
|
||||
|
||||
lhsIdent :: Assignment
|
||||
@ -435,7 +435,7 @@ unary = symbol Unary >>= \ location ->
|
||||
makeTerm location . Expression.Complement <$> children ( symbol AnonTilde *> expression )
|
||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonBang *> expression )
|
||||
<|> makeTerm location . Expression.Not <$> children ( symbol AnonNot *> expression )
|
||||
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier . name <$> source)) <*> some expression <*> emptyTerm)
|
||||
<|> makeTerm location <$> children (Expression.Call <$> pure [] <*> (makeTerm <$> symbol AnonDefinedQuestion <*> (Syntax.Identifier . name <$> tsource)) <*> some expression <*> emptyTerm)
|
||||
<|> makeTerm location . Expression.Negate <$> children ( symbol AnonMinus' *> expression )
|
||||
<|> children ( symbol AnonPlus *> expression )
|
||||
|
||||
|
@ -342,7 +342,7 @@ false :: Assignment
|
||||
false = makeTerm <$> symbol Grammar.False <*> (Literal.false <$ source)
|
||||
|
||||
identifier :: Assignment
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier . name <$> source)
|
||||
identifier = makeTerm <$> (symbol Identifier <|> symbol Identifier') <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
class' :: Assignment
|
||||
class' = makeClass <$> symbol Class <*> children ((,,,,) <$> manyTerm decorator <*> term identifier <*> (symbol TypeParameters *> children (manyTerm typeParameter') <|> pure []) <*> (classHeritage' <|> pure []) <*> classBodyStatements)
|
||||
@ -395,7 +395,7 @@ jsxAttribute = makeTerm <$> symbol Grammar.JsxAttribute <*> children (TypeScript
|
||||
where jsxAttributeValue = choice [ string, jsxExpression', jsxElement', jsxFragment ]
|
||||
|
||||
propertyIdentifier :: Assignment
|
||||
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier . name <$> source)
|
||||
propertyIdentifier = makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
sequenceExpression :: Assignment
|
||||
sequenceExpression = makeTerm <$> symbol Grammar.SequenceExpression <*> children (Expression.SequenceExpression <$> term expression <*> term expressions)
|
||||
@ -410,7 +410,7 @@ parameter =
|
||||
<|> optionalParameter
|
||||
|
||||
accessibilityModifier' :: Assignment
|
||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier . name <$> source)
|
||||
accessibilityModifier' = makeTerm <$> symbol AccessibilityModifier <*> children (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
destructuringPattern :: Assignment
|
||||
destructuringPattern = object <|> array
|
||||
@ -638,7 +638,7 @@ labeledStatement :: Assignment
|
||||
labeledStatement = makeTerm <$> symbol Grammar.LabeledStatement <*> children (TypeScript.Syntax.LabeledStatement <$> statementIdentifier <*> term statement)
|
||||
|
||||
statementIdentifier :: Assignment
|
||||
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier . name <$> source)
|
||||
statementIdentifier = makeTerm <$> symbol StatementIdentifier <*> (Syntax.Identifier . name <$> tsource)
|
||||
|
||||
importStatement :: Assignment
|
||||
importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> children ((,) <$> importClause <*> fromClause)
|
||||
@ -668,12 +668,12 @@ importStatement = makeImportTerm <$> symbol Grammar.ImportStatement <*> childr
|
||||
makeImportTerm loc ([x], from) = makeImportTerm1 loc from x
|
||||
makeImportTerm loc (xs, from) = makeTerm loc $ fmap (makeImportTerm1 loc from) xs
|
||||
importSymbol = symbol Grammar.ImportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> ((Just <$> rawIdentifier) <|> pure Nothing))
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> tsource)
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
|
||||
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
|
||||
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
|
||||
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> tsource)
|
||||
|
||||
debuggerStatement :: Assignment
|
||||
debuggerStatement = makeTerm <$> symbol Grammar.DebuggerStatement <*> (TypeScript.Syntax.Debugger <$ source)
|
||||
@ -727,16 +727,16 @@ exportStatement = makeTerm <$> symbol Grammar.ExportStatement <*> children (flip
|
||||
<|> symbol Grammar.ExportSpecifier *> children (makeNameAliasPair <$> rawIdentifier <*> pure Nothing)
|
||||
makeNameAliasPair from (Just alias) = (from, alias)
|
||||
makeNameAliasPair from Nothing = (from, from)
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> source)
|
||||
rawIdentifier = (symbol Identifier <|> symbol Identifier') *> (name <$> tsource)
|
||||
-- TODO: Need to validate that inline comments are still handled with this change in assigning to Path and not a Term.
|
||||
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source)
|
||||
fromClause = symbol Grammar.String *> (TypeScript.Syntax.importPath <$> tsource)
|
||||
|
||||
propertySignature :: Assignment
|
||||
propertySignature = makePropertySignature <$> symbol Grammar.PropertySignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm))
|
||||
where makePropertySignature loc (modifier, readonly, propertyName, annotation) = makeTerm loc (TypeScript.Syntax.PropertySignature [modifier, readonly, annotation] propertyName)
|
||||
|
||||
propertyName :: Assignment
|
||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier . name <$> source)) <|> term string <|> term number <|> term computedPropertyName
|
||||
propertyName = (makeTerm <$> symbol PropertyIdentifier <*> (Syntax.Identifier . name <$> tsource)) <|> term string <|> term number <|> term computedPropertyName
|
||||
|
||||
computedPropertyName :: Assignment
|
||||
computedPropertyName = makeTerm <$> symbol Grammar.ComputedPropertyName <*> children (TypeScript.Syntax.ComputedPropertyName <$> term expression)
|
||||
@ -798,7 +798,7 @@ variableDeclarator =
|
||||
requireCall = symbol CallExpression *> children ((symbol Identifier <|> symbol Identifier') *> do
|
||||
s <- source
|
||||
guard (s == "require")
|
||||
symbol Arguments *> children (symbol Grammar.String *> (TypeScript.Syntax.importPath <$> source))
|
||||
symbol Arguments *> children (symbol Grammar.String *> (TypeScript.Syntax.importPath <$> tsource))
|
||||
)
|
||||
|
||||
|
||||
|
@ -6,8 +6,7 @@ import Data.Abstract.Evaluatable
|
||||
import qualified Data.Abstract.Module as M
|
||||
import Data.Abstract.Package
|
||||
import Data.Abstract.Path
|
||||
import qualified Data.ByteString as B
|
||||
import qualified Data.ByteString.Char8 as BC
|
||||
import qualified Data.Text as T
|
||||
import Data.JSON.Fields
|
||||
import qualified Data.Language as Language
|
||||
import qualified Data.Map as Map
|
||||
@ -23,15 +22,16 @@ data Relative = Relative | NonRelative
|
||||
data ImportPath = ImportPath { unPath :: FilePath, pathIsRelative :: Relative }
|
||||
deriving (Eq, Generic, Hashable, Ord, Show)
|
||||
|
||||
importPath :: ByteString -> ImportPath
|
||||
importPath str = let path = stripQuotes str in ImportPath (BC.unpack path) (pathType path)
|
||||
-- TODO: fix the duplication present in this and Python
|
||||
importPath :: Text -> ImportPath
|
||||
importPath str = let path = stripQuotes str in ImportPath (T.unpack path) (pathType path)
|
||||
where
|
||||
stripQuotes = B.filter (`B.notElem` "\'\"")
|
||||
pathType xs | not (B.null xs), BC.head xs == '.' = Relative
|
||||
stripQuotes = T.dropAround (`elem` ("\'\"" :: String))
|
||||
pathType xs | not (T.null xs), T.head xs == '.' = Relative -- TODO: fix partiality
|
||||
| otherwise = NonRelative
|
||||
|
||||
toName :: ImportPath -> Name
|
||||
toName = name . BC.pack . unPath
|
||||
toName = name . T.pack . unPath
|
||||
|
||||
-- Node.js resolution algorithm: https://nodejs.org/api/modules.html#modules_all_together
|
||||
--
|
||||
|
2
vendor/fastsum
vendored
2
vendor/fastsum
vendored
@ -1 +1 @@
|
||||
Subproject commit 2310af6de3d3c337d671cdf9fe3e007990fdb1e4
|
||||
Subproject commit dbeff0af57fcea85bca07ff5a8149301dd3b084c
|
Loading…
Reference in New Issue
Block a user