mirror of
https://github.com/github/semantic.git
synced 2024-12-24 07:25:44 +03:00
Rename fields from visibility -> accessControl
This commit is contained in:
parent
27feb45a4b
commit
2eccafcecb
@ -89,7 +89,7 @@ instance AccessControls1 Data.Syntax.Declaration.AccessControl where
|
||||
liftTermToAccessControl _ Data.Syntax.Declaration.Unknown = Just ScopeGraph.Unknown
|
||||
|
||||
data Method a = Method { methodContext :: [a]
|
||||
, methodVisibility :: a
|
||||
, methodAccessControl :: a
|
||||
, methodReceiver :: a
|
||||
, methodName :: a
|
||||
, methodParameters :: [a]
|
||||
@ -106,7 +106,7 @@ instance Evaluatable Method where
|
||||
eval _ _ Method{..} = do
|
||||
name <- maybeM (throwNoNameError methodName) (declaredName methodName)
|
||||
span <- ask @Span
|
||||
let accessControl = fromMaybe ScopeGraph.Public (termToAccessControl methodVisibility)
|
||||
let accessControl = fromMaybe ScopeGraph.Public (termToAccessControl methodAccessControl)
|
||||
associatedScope <- declareFunction name Default accessControl span
|
||||
|
||||
params <- withScope associatedScope $ do
|
||||
@ -133,7 +133,11 @@ instance FreeVariables1 Method where
|
||||
|
||||
|
||||
-- | A method signature in TypeScript or a method spec in Go.
|
||||
data MethodSignature a = MethodSignature { methodSignatureContext :: ![a], methodSignatureName :: !a, methodSignatureParameters :: ![a] }
|
||||
data MethodSignature a = MethodSignature { methodSignatureContext :: [a]
|
||||
, methodSignatureAccessControl :: a
|
||||
, methodSignatureName :: a
|
||||
, methodSignatureParameters :: [a]
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
deriving (Eq1, Show1, Ord1) via Generically MethodSignature
|
||||
|
||||
@ -199,8 +203,8 @@ instance Declarations a => Declarations (InterfaceDeclaration a) where
|
||||
|
||||
-- | A public field definition such as a field definition in a JavaScript class.
|
||||
data PublicFieldDefinition a = PublicFieldDefinition { publicFieldContext :: [a]
|
||||
, publicFieldAccessControl :: a
|
||||
, publicFieldPropertyName :: a
|
||||
, publicFieldVisibility :: a
|
||||
, publicFieldValue :: a
|
||||
}
|
||||
deriving (Declarations1, Diffable, Eq, Foldable, FreeVariables1, Functor, Generic1, Hashable1, Ord, Show, ToJSONFields1, Traversable, Named1, Message1, NFData1)
|
||||
@ -212,7 +216,7 @@ instance Evaluatable PublicFieldDefinition where
|
||||
span <- ask @Span
|
||||
propertyName <- maybeM (throwNoNameError publicFieldPropertyName) (declaredName publicFieldPropertyName)
|
||||
|
||||
declare (Declaration propertyName) Instance (fromMaybe ScopeGraph.Public (termToAccessControl publicFieldVisibility)) span Nothing
|
||||
declare (Declaration propertyName) Instance (fromMaybe ScopeGraph.Public (termToAccessControl publicFieldAccessControl)) span Nothing
|
||||
slot <- lookupSlot (Declaration propertyName)
|
||||
value <- eval publicFieldValue
|
||||
assign slot value
|
||||
|
@ -31,13 +31,13 @@ import Data.ImportPath (importPath, defaultAlias)
|
||||
|
||||
type Syntax =
|
||||
'[ Comment.Comment
|
||||
, Declaration.AccessControl
|
||||
, Declaration.Constructor
|
||||
, Declaration.Function
|
||||
, Declaration.Method
|
||||
, Declaration.MethodSignature
|
||||
, Declaration.Type
|
||||
, Declaration.TypeAlias
|
||||
, Declaration.AccessControl
|
||||
, Expression.Plus
|
||||
, Expression.Minus
|
||||
, Expression.Times
|
||||
@ -459,21 +459,23 @@ indexExpression :: Assignment Term
|
||||
indexExpression = makeTerm <$> symbol IndexExpression <*> children (Expression.Subscript <$> expression <*> manyTerm expression)
|
||||
|
||||
methodDeclaration :: Assignment Term
|
||||
methodDeclaration = makeTerm <$> symbol MethodDeclaration <*> children (mkTypedMethodDeclaration <$> receiver <*> accessibility <*> term fieldIdentifier <*> params <*> returnParameters <*> (term block <|> emptyTerm))
|
||||
methodDeclaration = makeTerm <$> symbol MethodDeclaration <*> children (mkTypedMethodDeclaration <$> receiver <*> unknownAccessControl <*> term fieldIdentifier <*> params <*> returnParameters <*> (term block <|> emptyTerm))
|
||||
where
|
||||
params = symbol ParameterList *> children (manyTerm expression)
|
||||
receiver = symbol ParameterList *> children expressions
|
||||
mkTypedMethodDeclaration receiver' accessibility' name' parameters' type'' body' = Declaration.Method type'' accessibility' receiver' name' parameters' body'
|
||||
accessibility = makeTerm <$> location <*> pure Declaration.Unknown
|
||||
mkTypedMethodDeclaration receiver' accessControl name' parameters' type'' body' = Declaration.Method type'' accessControl receiver' name' parameters' body'
|
||||
returnParameters = (symbol ParameterList *> children (manyTerm expression))
|
||||
<|> pure <$> expression
|
||||
<|> pure []
|
||||
|
||||
methodSpec :: Assignment Term
|
||||
methodSpec = makeTerm <$> symbol MethodSpec <*> children (mkMethodSpec <$> expression <*> params <*> (expression <|> emptyTerm))
|
||||
methodSpec = makeTerm <$> symbol MethodSpec <*> children (mkMethodSpec <$> unknownAccessControl <*> expression <*> params <*> (expression <|> emptyTerm))
|
||||
where
|
||||
params = symbol ParameterList *> children (manyTerm expression)
|
||||
mkMethodSpec name' params optionalTypeLiteral = Declaration.MethodSignature [optionalTypeLiteral] name' params
|
||||
mkMethodSpec accessControl name' params optionalTypeLiteral = Declaration.MethodSignature [optionalTypeLiteral] accessControl name' params
|
||||
|
||||
unknownAccessControl :: Assignment Term
|
||||
unknownAccessControl = makeTerm <$> location <*> pure Declaration.Unknown
|
||||
|
||||
methodSpecList :: Assignment Term
|
||||
methodSpecList = symbol MethodSpecList *> children expressions
|
||||
|
@ -505,7 +505,7 @@ readonly' = makeTerm <$> symbol Readonly <*> (Type.Readonly <$ rawSource)
|
||||
methodDefinition :: Assignment Term
|
||||
methodDefinition = makeMethod <$>
|
||||
symbol MethodDefinition
|
||||
<*> children ((,,,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> emptyTerm <*> term propertyName <*> callSignatureParts <*> term statementBlock)
|
||||
<*> children ((,,,,,) <$> (term accessibilityModifier' <|> publicAccessControl) <*> (term readonly' <|> emptyTerm) <*> emptyTerm <*> term propertyName <*> callSignatureParts <*> term statementBlock)
|
||||
where
|
||||
makeMethod loc (modifier, readonly, receiver, propertyName', (typeParameters', params, ty'), statements) = makeTerm loc (Declaration.Method [readonly, typeParameters', ty'] modifier receiver propertyName' params statements)
|
||||
|
||||
@ -530,8 +530,8 @@ indexSignature :: Assignment Term
|
||||
indexSignature = makeTerm <$> symbol Grammar.IndexSignature <*> children (TypeScript.Syntax.IndexSignature <$> term identifier <*> predefinedTy <*> term typeAnnotation')
|
||||
|
||||
methodSignature :: Assignment Term
|
||||
methodSignature = makeMethodSignature <$> symbol Grammar.MethodSignature <*> children ((,,,) <$> (term accessibilityModifier' <|> emptyTerm) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> callSignatureParts)
|
||||
where makeMethodSignature loc (modifier, readonly, propertyName, (typeParams, params, annotation)) = makeTerm loc (Declaration.MethodSignature [modifier, readonly, typeParams, annotation] propertyName params)
|
||||
methodSignature = makeMethodSignature <$> symbol Grammar.MethodSignature <*> children ((,,,) <$> (term accessibilityModifier' <|> publicAccessControl) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> callSignatureParts)
|
||||
where makeMethodSignature loc (accessControl, readonly, propertyName, (typeParams, params, annotation)) = makeTerm loc (Declaration.MethodSignature [readonly, typeParams, annotation] accessControl propertyName params)
|
||||
|
||||
formalParameters :: Assignment [Term]
|
||||
formalParameters = symbol FormalParameters *> children (contextualize' <$> Assignment.manyThrough comment (postContextualize' <$> (concat <$> many ((\as b -> as <> [b]) <$> manyTerm decorator <*> term parameter)) <*> many comment))
|
||||
@ -679,7 +679,7 @@ publicAccessControl = makeTerm <$> location <*> pure Declaration.Public
|
||||
|
||||
publicFieldDefinition :: Assignment Term
|
||||
publicFieldDefinition = makeField <$> symbol Grammar.PublicFieldDefinition <*> children ((,,,,) <$> (term accessibilityModifier' <|> term publicAccessControl) <*> (term readonly' <|> emptyTerm) <*> term propertyName <*> (term typeAnnotation' <|> emptyTerm) <*> (term expression <|> emptyTerm))
|
||||
where makeField loc (modifier, readonly, propertyName, annotation, expression) = makeTerm loc (Declaration.PublicFieldDefinition [readonly, annotation] propertyName modifier expression)
|
||||
where makeField loc (accessControl, readonly, propertyName, annotation, expression) = makeTerm loc (Declaration.PublicFieldDefinition [readonly, annotation] accessControl propertyName expression)
|
||||
|
||||
|
||||
statement :: Assignment Term
|
||||
|
Loading…
Reference in New Issue
Block a user