Allow to interleave visibility and function modifiers
[hiphop-php.git] / hphp / hack / src / server / ffpAutocompleteContextParser.ml
blobb6dd41b6a194739748f39c6c9033697c145e5e5f
1 (**
2 * Copyright (c) 2017, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the BSD-style license found in the
6 * LICENSE file in the "hack" directory of this source tree. An additional grant
7 * of patent rights can be found in the PATENTS file in the same directory.
9 *)
11 module PositionedSyntax = Full_fidelity_positioned_syntax
12 module PositionedToken = Full_fidelity_positioned_token
13 module SyntaxKind = Full_fidelity_syntax_kind
14 module SyntaxTree = Full_fidelity_syntax_tree
15 module TokenKind = Full_fidelity_token_kind
17 open Hh_core
19 module Container = struct
20 (* Set of mutually exclusive contexts. *)
21 type t =
22 | AfterDoubleColon
23 | AfterRightArrow
24 | AssignmentExpression
25 | ClassBody
26 | ClassHeader
27 | CompoundStatement
28 | ConstantDeclaration
29 | FunctionCallArgumentList
30 | FunctionHeader
31 | IfStatement
32 | InterfaceBody
33 | InterfaceHeader
34 | LambdaBodyExpression
35 | TopLevel
36 | TraitBody
37 | TraitHeader
38 | NoContainer
39 end
41 module Predecessor = struct
42 type t =
43 | ClassBodyDeclaration
44 | ClassName
45 | IfWithoutElse
46 | ImplementsList
47 | ExtendsList
48 | KeywordAbstract
49 | KeywordAsync
50 | KeywordAwait
51 | KeywordCase
52 | KeywordClass
53 | KeywordConst
54 | KeywordElse
55 | KeywordEnum
56 | KeywordExtends
57 | KeywordFinal
58 | KeywordFunction
59 | KeywordImplements
60 | KeywordInclude
61 | KeywordInterface
62 | KeywordNamespace
63 | KeywordNew
64 | KeywordNewtype
65 | KeywordRequire
66 | KeywordReturn
67 | KeywordStatic
68 | KeywordSwitch
69 | KeywordTrait
70 | KeywordType
71 | KeywordUse
72 | Statement
73 | TokenColon
74 | TokenComma
75 | TokenEqual
76 | TokenLeftBrace
77 | TokenLessThan
78 | TokenOpenParen
79 | TokenWithoutTrailingTrivia
80 | TopLevelDeclaration
81 | TryWithoutFinally
82 | VisibilityModifier
83 | NoPredecessor
84 end
86 type context = {
87 closest_parent_container: Container.t;
88 inside_async_function: bool;
89 inside_class_body: bool;
90 inside_loop_body: bool;
91 inside_static_method: bool;
92 inside_switch_body: bool;
93 predecessor: Predecessor.t;
96 module ContextPredicates = struct
97 open Container
98 open Predecessor
100 let is_inside_function_call context =
101 context.closest_parent_container = FunctionCallArgumentList &&
102 (context.predecessor = TokenComma ||
103 context.predecessor = TokenOpenParen ||
104 context.predecessor = TokenWithoutTrailingTrivia)
106 let is_type_valid context =
107 (* Function return type *)
108 context.closest_parent_container = FunctionHeader &&
109 context.predecessor = TokenColon
110 || (* Parameter type *)
111 context.closest_parent_container = FunctionHeader &&
112 (context.predecessor = TokenComma ||
113 context.predecessor = TokenOpenParen ||
114 context.predecessor = TokenWithoutTrailingTrivia)
115 || (* Class property type *)
116 (context.closest_parent_container = ClassBody ||
117 context.closest_parent_container = TraitBody) &&
118 (context.predecessor = VisibilityModifier ||
119 context.predecessor = KeywordConst ||
120 context.predecessor = KeywordStatic)
121 || (* Generic type *)
122 context.predecessor = TokenLessThan
124 let is_class_body_declaration_valid context =
125 context.closest_parent_container = ClassBody &&
126 (context.predecessor = TokenLeftBrace ||
127 context.predecessor = ClassBodyDeclaration)
129 let is_trait_body_declaration_valid context =
130 context.closest_parent_container = TraitBody &&
131 (context.predecessor = TokenLeftBrace ||
132 context.predecessor = ClassBodyDeclaration)
134 let is_interface_body_declaration_valid context =
135 context.closest_parent_container = InterfaceBody &&
136 (context.predecessor = TokenLeftBrace ||
137 context.predecessor = ClassBodyDeclaration)
139 let is_in_return_statement context =
140 context.predecessor = KeywordReturn &&
141 context.closest_parent_container = CompoundStatement
143 let is_at_beginning_of_new_statement context =
144 context.closest_parent_container = CompoundStatement &&
145 (context.predecessor = Statement ||
146 context.predecessor = TokenLeftBrace ||
147 context.predecessor = IfWithoutElse ||
148 context.predecessor = TryWithoutFinally)
149 || (* Cases in a switch body *)
150 context.closest_parent_container = CompoundStatement &&
151 context.predecessor = TokenColon
153 let is_rhs_of_assignment_expression context =
154 context.closest_parent_container = AssignmentExpression &&
155 context.predecessor = TokenEqual
157 let is_in_conditional context =
158 context.closest_parent_container = IfStatement &&
159 (context.predecessor = TokenOpenParen ||
160 context.predecessor = TokenWithoutTrailingTrivia)
162 let is_expression_valid context =
163 is_rhs_of_assignment_expression context ||
164 is_in_conditional context ||
165 is_at_beginning_of_new_statement context ||
166 is_in_return_statement context ||
167 is_inside_function_call context ||
168 context.closest_parent_container = LambdaBodyExpression
169 (* TODO: or is parameter, or is inside if/switch/while/etc. clause *)
171 let is_top_level_statement_valid context =
172 context.closest_parent_container = TopLevel &&
173 context.predecessor = TopLevelDeclaration
176 let initial_context = {
177 closest_parent_container = Container.NoContainer;
178 inside_async_function = false;
179 inside_class_body = false;
180 inside_loop_body = false;
181 inside_static_method = false;
182 inside_switch_body = false;
183 predecessor = Predecessor.NoPredecessor;
186 let validate_predecessor (predecessor:PositionedSyntax.t list) : Predecessor.t =
187 let open PositionedSyntax in
188 let open PositionedToken in
189 let open TokenKind in
190 let open Predecessor in
191 let classify_syntax_as_predecessor node = match syntax node with
192 | AliasDeclaration { alias_semicolon = { syntax = Token _; _ }; _ }
193 | EnumDeclaration { enum_right_brace = { syntax = Token _; _ }; _ }
194 | FunctionDeclaration { function_body = { syntax =
195 CompoundStatement { compound_right_brace = { syntax =
196 Token _; _
197 }; _ }; _
198 }; _ }
199 | InclusionDirective { inclusion_semicolon = { syntax = Token _; _ }; _ }
200 | MarkupSection _
201 | NamespaceBody { namespace_right_brace = { syntax = Token _; _ }; _ }
202 | NamespaceEmptyBody { namespace_semicolon = { syntax = Token _; _ }; _ }
203 | NamespaceUseDeclaration { namespace_use_semicolon = { syntax = Token _; _ }; _ }
204 | ClassishBody { classish_body_right_brace = { syntax = Token _; _ }; _ } ->
205 Some TopLevelDeclaration
206 | ClassishDeclaration {
207 classish_implements_list = { syntax = SyntaxList _; _ }; _
208 } -> Some ImplementsList
209 | ClassishDeclaration {
210 classish_extends_list = { syntax = SyntaxList _; _ };
211 classish_implements_keyword = { syntax = Missing; _ };
212 classish_implements_list = { syntax = Missing; _ };
214 } -> Some ExtendsList
215 | ClassishDeclaration {
216 classish_name = { syntax = Token _; _ };
217 classish_type_parameters = { syntax = Missing; _ };
218 classish_extends_keyword = { syntax = Missing; _ };
219 classish_extends_list = { syntax = Missing; _ };
220 classish_implements_keyword = { syntax = Missing; _ };
221 classish_implements_list = { syntax = Missing; _ };
223 } -> Some ClassName
224 | IfStatement { if_else_clause = {
225 syntax = Missing; _
226 }; _ } -> Some IfWithoutElse
227 | TryStatement { try_finally_clause = {
228 syntax = Missing; _
229 }; _ } -> Some TryWithoutFinally
230 | CaseLabel _
231 | IfStatement _
232 | EchoStatement _
233 | WhileStatement _
234 | DoStatement _
235 | ForStatement _
236 | ForeachStatement _
237 | TryStatement _
238 | SwitchStatement _
239 | ReturnStatement _
240 | ThrowStatement _
241 | BreakStatement _
242 | ContinueStatement _
243 | ExpressionStatement _ -> Some Statement
244 | TraitUse _
245 | RequireClause _
246 | ConstDeclaration _
247 | PropertyDeclaration _
248 | MethodishDeclaration _
249 | TypeConstDeclaration _ -> Some ClassBodyDeclaration
250 | Token { kind = Abstract; _ } -> Some KeywordAbstract
251 | Token { kind = Async; _ } -> Some KeywordAsync
252 | Token { kind = Await; _ } -> Some KeywordAwait
253 | Token { kind = Case; _ } -> Some KeywordCase
254 | Token { kind = Class; _ } -> Some KeywordClass
255 | Token { kind = Colon; _ } -> Some TokenColon
256 | Token { kind = Comma; _ } -> Some TokenComma
257 | Token { kind = Const; _ } -> Some KeywordConst
258 | Token { kind = Else; _ } -> Some KeywordElse
259 | Token { kind = Enum; _ } -> Some KeywordEnum
260 | Token { kind = Equal; _ } -> Some TokenEqual
261 | Token { kind = Extends; _ } -> Some KeywordExtends
262 | Token { kind = Final; _ } -> Some KeywordFinal
263 | Token { kind = Function; _ } -> Some KeywordFunction
264 | Token { kind = Implements; _ } -> Some KeywordImplements
265 | Token { kind = Include; _ }
266 | Token { kind = Include_once; _ } -> Some KeywordInclude
267 | Token { kind = Interface; _ } -> Some KeywordInterface
268 | Token { kind = LeftBrace; _ } -> Some TokenLeftBrace
269 | Token { kind = LeftParen; _ } -> Some TokenOpenParen
270 | Token { kind = LessThan; _ } -> Some TokenLessThan
271 | Token { kind = Namespace; _ } -> Some KeywordNamespace
272 | Token { kind = New; _ } -> Some KeywordNew
273 | Token { kind = Newtype; _ } -> Some KeywordNewtype
274 | Token { kind = Public; _ }
275 | Token { kind = Private; _ }
276 | Token { kind = Protected; _ } -> Some VisibilityModifier
277 | Token { kind = Require; _ } -> Some KeywordRequire
278 | Token { kind = Return; _ } -> Some KeywordReturn
279 | Token { kind = Static; _ } -> Some KeywordStatic
280 | Token { kind = Switch; _ } -> Some KeywordSwitch
281 | Token { kind = Trait; _ } -> Some KeywordTrait
282 | Token { kind = Type; _ } -> Some KeywordType
283 | Token { kind = Use; _ } -> Some KeywordUse
284 | Token { trailing_width = 0; _ } -> Some TokenWithoutTrailingTrivia
285 | _ -> None
287 predecessor
288 |> List.find_map ~f:classify_syntax_as_predecessor
289 |> Option.value ~default:NoPredecessor
291 let is_method_static (method_object:PositionedSyntax.syntax) : bool =
292 let open PositionedSyntax in
293 let open PositionedToken in
294 let open TokenKind in
295 match method_object with
296 | MethodishDeclaration {
297 methodish_function_decl_header = {
298 syntax = FunctionDeclarationHeader h; _
299 }; _
300 } ->
301 List.exists (syntax_node_to_list h.function_modifiers) ~f:(is_specific_token Static)
302 | AnonymousFunction { anonymous_static_keyword = static; _ } ->
303 is_specific_token Static static
304 | _ -> false
306 let is_function_async (function_object:PositionedSyntax.syntax) : bool =
307 let open PositionedSyntax in
308 let open PositionedToken in
309 let open TokenKind in
310 match function_object with
311 | FunctionDeclaration {
312 function_declaration_header = { syntax = FunctionDeclarationHeader {
313 function_modifiers = m; _
314 }; _ }; _
316 | MethodishDeclaration { methodish_function_decl_header = { syntax =
317 FunctionDeclarationHeader { function_modifiers = m; _ }; _
318 }; _ } ->
319 List.exists (syntax_node_to_list m) ~f:is_async
320 | AnonymousFunction { anonymous_async_keyword = async; _ }
321 | LambdaExpression { lambda_async = async; _ } ->
322 is_specific_token Async async
323 | _ -> false
325 let make_context
326 ~(full_path:PositionedSyntax.t list)
327 ~(predecessor:PositionedSyntax.t list)
328 : context =
329 let predecessor = validate_predecessor predecessor in
330 let open PositionedSyntax in
331 let open Container in
332 let open PositionedToken in
333 let open TokenKind in
334 let check_node node acc = match syntax node with
335 | Script _ ->
336 { acc with closest_parent_container = TopLevel }
337 | ClassishDeclaration { classish_keyword = {
338 syntax = Token { kind = Interface; _ }; _
339 }; _ } ->
340 { acc with closest_parent_container = InterfaceHeader }
341 | ClassishDeclaration { classish_keyword = {
342 syntax = Token { kind = Trait; _ }; _
343 }; _ } ->
344 { acc with closest_parent_container = TraitHeader }
345 | ClassishDeclaration _ ->
346 { acc with closest_parent_container = ClassHeader }
347 | ClassishBody _ when acc.closest_parent_container = InterfaceHeader ->
348 { acc with closest_parent_container = InterfaceBody }
349 | ClassishBody _ when acc.closest_parent_container = TraitHeader ->
350 { acc with closest_parent_container = TraitBody }
351 | ClassishBody _ when acc.closest_parent_container = ClassHeader ->
352 { acc with closest_parent_container = ClassBody;
353 inside_class_body = true }
354 | ConstDeclaration _ ->
355 { acc with closest_parent_container = ConstantDeclaration }
356 | ForStatement _
357 | ForeachStatement _
358 | WhileStatement _
359 | DoStatement _ ->
360 { acc with inside_loop_body = true }
361 | SwitchSection _ ->
362 { acc with closest_parent_container = Container.CompoundStatement;
363 inside_switch_body = true }
364 | MethodishDeclaration _
365 | FunctionDeclaration _ as func ->
366 { acc with inside_async_function = is_function_async func;
367 inside_static_method = is_method_static func }
368 | FunctionDeclarationHeader _ ->
369 { acc with closest_parent_container = FunctionHeader }
370 | FunctionCallExpression _ ->
371 { acc with closest_parent_container = FunctionCallArgumentList }
372 | AnonymousFunction _
373 | LambdaExpression _ as lambda ->
374 (* If we see a lambda, almost all context is reset, so each field should
375 get consideration on if its context flows into the lambda *)
377 closest_parent_container = LambdaBodyExpression;
378 predecessor = predecessor;
379 inside_switch_body = false;
380 inside_loop_body = false;
381 inside_class_body = false;
382 inside_static_method = is_method_static lambda;
383 inside_async_function = is_function_async lambda;
385 | PositionedSyntax.CompoundStatement _ ->
386 { acc with closest_parent_container = Container.CompoundStatement }
387 | BinaryExpression {
388 binary_operator = { syntax = Token { kind = Equal; _ }; _ };
390 } -> { acc with closest_parent_container = AssignmentExpression }
391 | PositionedSyntax.IfStatement _ ->
392 { acc with closest_parent_container = Container.IfStatement }
393 | Token { kind = ColonColon; _ } ->
394 { acc with closest_parent_container = AfterDoubleColon }
395 | Token { kind = MinusGreaterThan; _ } ->
396 { acc with closest_parent_container = AfterRightArrow }
397 | _ -> acc
399 List.fold_right
400 ~f:check_node
401 ~init:{ initial_context with predecessor }
402 full_path
404 type autocomplete_location_classification =
405 | BeforePunctuationToken
406 | InLeadingTrivia
407 | InToken
408 | InTrailingTrivia
410 let classify_autocomplete_location
411 (parents:PositionedSyntax.t list) (offset:int)
412 : autocomplete_location_classification =
413 let open PositionedSyntax in
414 let check_for_specific_token parent =
415 let open PositionedToken in
416 match syntax parent with
417 | Token { kind = TokenKind.EndOfFile; _ } -> InLeadingTrivia
418 | Token { kind = TokenKind.RightParen; _ } -> BeforePunctuationToken
419 | _ -> InToken
421 match parents with
422 | [] -> failwith "Empty parentage (this should never happen)"
423 | parent :: _ when offset < start_offset parent -> InLeadingTrivia
424 | parent :: _ when offset = start_offset parent -> check_for_specific_token parent
425 | parent :: _ when offset <= trailing_start_offset parent -> InToken
426 | _ -> InTrailingTrivia
428 let get_context_and_stub (positioned_tree:PositionedSyntax.t) (offset:int)
429 : context * string =
430 let open PositionedSyntax in
431 (* If the offset is the same as the width of the whole tree, then the cursor is at the end of
432 file, so we move our position to before the last character of the file so that our cursor is
433 considered to be in the leading trivia of the end of file character. This guarantees our parentage
434 is not empty. *)
435 let new_offset =
436 if offset >= full_width positioned_tree then full_width positioned_tree - 1
437 else offset
439 let ancestry = parentage positioned_tree new_offset in
440 let location = classify_autocomplete_location ancestry offset in
441 let autocomplete_leaf_node = List.hd_exn ancestry in
442 let previous_offset = leading_start_offset autocomplete_leaf_node - 1 in
443 let predecessor_parentage = parentage positioned_tree previous_offset in
444 let validate_hack_identifier id =
445 let identifier_regex = Str.regexp "^\\$?[a-zA-Z0-9_\x7f-\xff]*$" in
446 if Str.string_match identifier_regex id 0 then id else ""
448 let node_text = match location with
449 | InToken -> validate_hack_identifier @@ text @@ List.hd_exn ancestry
450 | BeforePunctuationToken ->
451 validate_hack_identifier @@ text @@ List.hd_exn predecessor_parentage
452 | _ -> ""
454 let (full_path, predecessor) = match location with
455 | BeforePunctuationToken
456 | InLeadingTrivia -> predecessor_parentage, predecessor_parentage
457 | InToken -> ancestry, predecessor_parentage
458 | InTrailingTrivia -> ancestry, ancestry
460 (make_context ~full_path ~predecessor, node_text)