Check argument to 'unset' in reactive mode
[hiphop-php.git] / hphp / hack / src / hackfmt.ml
blob4c739fa742e97f5b4feb76a45c587b00c720be19
1 (**
2 * Copyright (c) 2016, Facebook, Inc.
3 * All rights reserved.
5 * This source code is licensed under the MIT license found in the
6 * LICENSE file in the "hack" directory of this source tree.
8 *)
10 module SyntaxTree = Full_fidelity_syntax_tree
11 module SourceText = Full_fidelity_source_text
12 module Logger = HackfmtEventLogger
13 module FEnv = Format_env
15 open Hh_core
16 open Printf
17 open Libhackfmt
18 open Hackfmt_error
19 open Ocaml_overrides
21 type filename = string
23 type range =
24 | Byte of Interval.t (* 0-based byte offsets; half-open/inclusive-exclusive *)
25 | Line of Interval.t (* 1-based line numbers; inclusive *)
27 type text_source =
28 | File of filename
29 | Stdin of filename option (* Optional filename for logging. *)
31 let text_source_to_filename = function
32 | File filename -> Some filename
33 | Stdin filename -> filename
35 module Env = struct
36 type t = {
37 debug: bool;
38 test: bool;
39 hacksperimental: bool;
40 mutable mode: string option;
41 mutable text_source: text_source;
42 mutable root: string;
44 end
46 let usage = sprintf
47 "Usage: %s [--range s e] [filename or read from stdin]\n" Sys.argv.(0)
49 let parse_options () =
50 let files = ref [] in
51 let filename_for_logging = ref None in
52 let start_char = ref None in
53 let end_char = ref None in
54 let start_line = ref None in
55 let end_line = ref None in
56 let at_char = ref None in
57 let inplace = ref false in
58 let indent_width = ref FEnv.(default.indent_width) in
59 let indent_with_tabs = ref FEnv.(default.indent_with_tabs) in
60 let line_width = ref FEnv.(default.line_width) in
61 let diff = ref false in
62 let root = ref None in
63 let diff_dry = ref false in
64 let debug = ref false in
65 let test = ref false in
66 let hacksperimental = ref false in
68 let rec options = ref [
69 "--range",
70 Arg.Tuple ([
71 Arg.Int (fun x -> start_char := Some x);
72 Arg.Int (fun x -> end_char := Some x);
73 ]),
74 "[start end] Range of character positions to be formatted (1 indexed)";
76 "--line-range",
77 Arg.Tuple ([
78 Arg.Int (fun x -> start_line := Some x);
79 Arg.Int (fun x -> end_line := Some x);
80 ]),
81 "[start end] Range of lines to be formatted (1 indexed, inclusive)";
83 "--at-char",
84 Arg.Int (fun x -> at_char := Some x),
85 "[idx] Format a node ending at the given character" ^
86 " (0 indexed)";
88 "-i", Arg.Set inplace, " Format file in-place";
89 "--in-place", Arg.Set inplace, " Format file in-place";
91 "--indent-width", Arg.Set_int indent_width,
92 sprintf
93 " Specify the number of spaces per indentation level. Defaults to %d"
94 FEnv.(default.indent_width);
96 "--line-width", Arg.Set_int line_width,
97 sprintf
98 " Specify the maximum length for each line. Defaults to %d"
99 FEnv.(default.line_width);
101 "--tabs", Arg.Set indent_with_tabs, " Indent with tabs rather than spaces";
103 "--diff",
104 Arg.Set diff,
105 " Format the changed lines in a diff" ^
106 " (example: hg diff | hackfmt --diff)";
108 "--root", Arg.String (fun x -> root := Some x),
109 "[dir] Specify a root directory for --diff mode";
111 "--diff-dry-run", Arg.Set diff_dry,
112 " Preview the files that would be overwritten by --diff mode";
114 "--debug",
115 Arg.Unit (fun () ->
116 debug := true;
117 options := Hackfmt_debug.init_with_options (); ),
118 " Print debug statements";
120 "--filename-for-logging",
121 Arg.String (fun x -> filename_for_logging := Some x),
122 " The filename for logging purposes, when providing file contents " ^
123 "through stdin.";
125 "--test", Arg.Set test, " Disable logging";
126 "--hacksperimental", Arg.Set hacksperimental, " Enable experimental features of Hack"
127 ] in
128 Arg.parse_dynamic options (fun file -> files := file :: !files) usage;
129 let range =
130 match !start_char, !end_char, !start_line, !end_line with
131 | Some s, Some e, None, None -> Some (Byte (s - 1, e - 1))
132 | None, None, Some s, Some e -> Some (Line (s, e))
133 | Some _, Some _, Some _, Some _ ->
134 raise (InvalidCliArg "Cannot use --range with --line-range")
135 | _ -> None
137 let config = FEnv.{default with
138 indent_width = !indent_width;
139 indent_with_tabs = !indent_with_tabs;
140 line_width = !line_width;
141 } in
142 (!files, !filename_for_logging, range, !at_char, !inplace, !diff, !root,
143 !diff_dry, config),
144 (!debug, !test, !hacksperimental)
146 let file_exists path = Option.is_some (Sys_utils.realpath path)
148 type format_options =
149 | Print of {
150 text_source: text_source;
151 range: range option;
152 config: FEnv.t;
154 | InPlace of {
155 filename: filename;
156 config: FEnv.t;
158 | AtChar of {
159 text_source: text_source;
160 pos: int;
161 config: FEnv.t;
163 | Diff of {
164 root: string option;
165 dry: bool;
166 config: FEnv.t;
169 let mode_string format_options =
170 match format_options with
171 | Print {text_source = File _; range = None; _} -> "FILE"
172 | Print {text_source = File _; range = Some _; _} -> "RANGE"
173 | Print {text_source = Stdin _; range = None; _} -> "STDIN"
174 | Print {text_source = Stdin _; range = Some _; _} -> "STDIN_RANGE"
175 | InPlace _ -> "IN_PLACE"
176 | AtChar _ -> "AT_CHAR"
177 | Diff {dry = false; _} -> "DIFF"
178 | Diff {dry = true; _} -> "DIFF_DRY"
180 type validate_options_input = {
181 text_source : text_source;
182 range : range option;
183 at_char : int option;
184 inplace : bool;
185 diff : bool;
188 let validate_options env
189 (files, filename_for_logging, range, at_char,
190 inplace, diff, root, diff_dry, config) =
191 let fail msg = raise (InvalidCliArg msg) in
192 let filename =
193 match files with
194 | [filename] -> Some filename
195 | [] -> None
196 | _ -> fail "More than one file given"
198 let text_source = match filename, filename_for_logging with
199 | Some _, Some _ ->
200 fail "Can't supply both a filename and a filename for logging"
201 | Some filename, None -> File filename
202 | None, Some filename_for_logging -> Stdin (Some filename_for_logging)
203 | None, None -> Stdin None
205 let assert_file_exists = function
206 | None -> ()
207 | Some path ->
208 if not (file_exists path) then
209 fail ("No such file or directory: " ^ path)
211 assert_file_exists filename;
212 assert_file_exists root;
214 (* Let --diff-dry-run imply --diff *)
215 let diff = diff || diff_dry in
217 match {diff; inplace; text_source; range; at_char} with
218 | _ when env.Env.debug && diff -> fail "Can't format diff in debug mode"
220 | {diff = true; text_source = File _; _}
221 | {diff = true; text_source = Stdin (Some _); _} -> fail "--diff mode expects no files"
222 | {diff = true; range = Some _; _} -> fail "--diff mode expects no range"
223 | {diff = true; at_char = Some _; _} -> fail "--diff mode can't format at-char"
225 | {inplace = true; text_source = Stdin _; _} -> fail "Provide a filename to format in-place"
226 | {inplace = true; range = Some _; _} -> fail "Can't format a range in-place"
227 | {inplace = true; at_char = Some _; _} -> fail "Can't format at-char in-place"
229 | {diff = false; inplace = false; range = Some _; at_char = Some _; _} ->
230 fail "--at-char expects no range"
232 | {diff = false; inplace = false; at_char = None; _} ->
233 Print {text_source; range; config}
234 | {diff = false; inplace = true; text_source = File filename; range = None; _} ->
235 InPlace {filename; config}
236 | {diff = false; inplace = false; range = None; at_char = Some pos; _} ->
237 AtChar {text_source; pos; config}
238 | {diff = true; text_source = Stdin None; range = None; _} ->
239 Diff {root; dry = diff_dry; config}
241 let read_stdin () =
242 let buf = Buffer.create 256 in
244 while true do
245 Buffer.add_string buf (read_line());
246 Buffer.add_char buf '\n';
247 done;
248 assert false
249 with End_of_file ->
250 Buffer.contents buf
252 let parse ~hacksperimental text_source =
253 let source_text =
254 match text_source with
255 | File filename ->
256 SourceText.from_file @@ Relative_path.create Relative_path.Dummy filename
257 | Stdin _ ->
258 SourceText.make Relative_path.default @@ read_stdin ()
260 let parser_env = Full_fidelity_parser_env.make ~hacksperimental () in
261 let tree = SyntaxTree.make ~env:parser_env source_text in
262 if List.is_empty (SyntaxTree.all_errors tree)
263 then tree
264 else raise Hackfmt_error.InvalidSyntax
266 let logging_time_taken env logger thunk =
267 let start_t = Unix.gettimeofday () in
268 let res = thunk () in
269 let end_t = Unix.gettimeofday () in
270 if not env.Env.test then
271 logger
272 ~start_t
273 ~end_t
274 ~mode:env.Env.mode
275 ~file:(text_source_to_filename env.Env.text_source)
276 ~root:env.Env.root;
279 (* If the range is a byte range, expand it to line boundaries.
280 * If the range is a line range, convert it to a byte range. *)
281 let expand_or_convert_range ?ranges source_text range =
282 match range with
283 | Byte range -> expand_to_line_boundaries ?ranges source_text range
284 | Line (st, ed) ->
285 let line_boundaries =
286 match ranges with
287 | Some ranges -> ranges
288 | None -> get_line_boundaries (SourceText.text source_text)
290 let st = max st 1 in
291 let ed = min ed (Array.length line_boundaries) in
292 try line_interval_to_offset_range line_boundaries (st, ed) with
293 | Invalid_argument msg -> raise (InvalidCliArg msg)
295 let format ?config ?range ?ranges env tree =
296 let source_text = SyntaxTree.text tree in
297 match range with
298 | None -> logging_time_taken env Logger.format_tree_end (fun () -> format_tree ?config tree)
299 | Some range ->
300 let range = expand_or_convert_range ?ranges source_text range in
301 logging_time_taken env Logger.format_range_end (fun () ->
302 let formatted = format_range ?config range tree in
303 (* This is a bit of a hack to deal with situations where a newline exists
304 * in the original source in a location where hackfmt refuses to split,
305 * and the range end falls at that newline. It is correct for format_range
306 * not to add the trailing newline, but it looks better to add an
307 * incorrect newline than to omit it, which would cause the following line
308 * (along with its indentation spaces) to be joined with the last line in
309 * the range. See test case: binary_expression_range_formatting.php *)
310 if formatted.[String.length formatted - 1] = '\n'
311 then formatted
312 else formatted ^ "\n"
315 let output ?text_source str =
316 let with_out_channel f =
317 match text_source with
318 | Some (File filename) ->
319 let out_channel = open_out filename in
320 f out_channel;
321 close_out out_channel
322 | Some (Stdin _)
323 | None -> f stdout
325 with_out_channel (fun out_channel -> fprintf out_channel "%s%!" str)
327 let rec guess_root config start recursion_limit =
328 if start = Path.parent start then None (* Reach fs root, nothing to do. *)
329 else if Wwwroot.is_www_directory ~config start then Some start
330 else if recursion_limit <= 0 then None
331 else guess_root config (Path.parent start) (recursion_limit - 1)
333 let get_root = function
334 | Some root -> Path.make root
335 | None ->
336 eprintf "No root specified, trying to guess one\n";
337 let config = ".hhconfig" in
338 let start_path = Path.make "." in
339 let root = match guess_root config start_path 50 with
340 | None -> start_path
341 | Some r -> r in
342 Wwwroot.assert_www_directory ~config root;
343 eprintf "Guessed root: %a\n%!" Path.output root;
344 root
346 let format_diff_intervals ?config env intervals tree =
348 logging_time_taken env Logger.format_intervals_end
349 (fun () -> format_intervals ?config intervals tree)
350 with
351 | Invalid_argument s -> raise (InvalidDiff s)
353 let debug_print ~hacksperimental ?range ?config text_source =
354 let tree = parse ~hacksperimental text_source in
355 let source_text = SyntaxTree.text tree in
356 let range = Option.map range (expand_or_convert_range source_text) in
357 let env = Libhackfmt.env_from_config config in
358 let doc = Hack_format.transform env (SyntaxTransforms.editable_from_positioned tree) in
359 let chunk_groups = Chunk_builder.build doc in
360 Hackfmt_debug.debug env ~range source_text tree doc chunk_groups
362 let main ~hacksperimental (env: Env.t) (options: format_options) =
363 env.Env.mode <- Some (mode_string options);
364 match options with
365 | Print {text_source; range; config} ->
366 env.Env.text_source <- text_source;
367 if env.Env.debug then
368 debug_print ~hacksperimental ?range ~config text_source
369 else
370 text_source
371 |> parse ~hacksperimental
372 |> format ?range ~config env
373 |> output
374 | InPlace {filename; config} ->
375 let text_source = File filename in
376 env.Env.text_source <- text_source;
377 if env.Env.debug then debug_print ~hacksperimental ~config text_source;
378 text_source
379 |> parse ~hacksperimental
380 |> format ~config env
381 |> output ~text_source
382 | AtChar {text_source; pos; config} ->
383 env.Env.text_source <- text_source;
384 let tree = parse ~hacksperimental text_source in
385 let range, formatted =
387 logging_time_taken env Logger.format_at_offset_end
388 (fun () -> format_at_offset ~config tree pos)
389 with
390 | Invalid_argument s -> raise (InvalidCliArg s) in
391 if env.Env.debug then debug_print ~hacksperimental text_source ~range:(Byte range) ~config;
392 Printf.printf "%d %d\n" (fst range) (snd range);
393 output formatted;
394 | Diff {root; dry; config} ->
395 let root = get_root root in
396 env.Env.root <- Path.to_string root;
397 read_stdin ()
398 |> Parse_diff.go
399 |> List.filter_map ~f:begin fun (rel_path, intervals) ->
400 (* We intentionally raise an exception here instead of printing a
401 * message and moving on--if a file is missing, it may be a signal that
402 * this diff is out of date and may lead us to format unexpected ranges
403 * (typically diffs will be directly piped from `hg diff`, and thus
404 * won't be out of date).
406 * Similarly, InvalidDiff exceptions thrown by format_diff_intervals
407 * (caused by out-of-bounds line numbers, etc) will cause us to bail
408 * before writing to any files. *)
409 let filename = Path.to_string (Path.concat root rel_path) in
410 if not (file_exists filename) then
411 raise (InvalidDiff ("No such file or directory: " ^ rel_path));
412 (* Store the name of the file we're working with, so if we encounter an
413 * exception, this filename will be the one that is logged. *)
414 let text_source = File filename in
415 env.Env.text_source <- text_source;
417 let contents =
418 text_source
419 |> parse ~hacksperimental
420 |> format_diff_intervals ~config env intervals in
421 Some (text_source, rel_path, contents)
422 with
423 (* A parse error isn't a signal that there's something wrong with the
424 * diff--there's just something wrong with that file. We can leave that
425 * file alone and move on. *)
426 | InvalidSyntax ->
427 Printf.eprintf "Parse error in file: %s\n%!" rel_path;
428 None
430 |> List.iter ~f:begin fun (text_source, rel_path, contents) ->
431 (* Log this filename in the event of an exception. *)
432 env.Env.text_source <- text_source;
433 if dry then printf "*** %s\n" rel_path;
434 let output_text_source = if dry then Stdin None else text_source in
435 output ~text_source:output_text_source contents
438 let () =
439 (* no-op, needed at entry point for the Daemon module (used by
440 HackfmtEventLogger) to behave correctly *)
441 Daemon.check_entry_point ();
443 let options, (debug, test, hacksperimental) = parse_options () in
444 let env = { Env.
445 debug;
446 test;
447 mode = None;
448 text_source = Stdin None;
449 root = Sys.getcwd ();
450 hacksperimental;
451 } in
453 let start_time = Unix.gettimeofday () in
454 if not env.Env.test then Logger.init start_time;
457 let options = validate_options env options in
458 main ~hacksperimental env options;
460 let time_taken = Unix.gettimeofday () -. start_time in
461 if not env.Env.test then
462 Logger.exit
463 ~time_taken
464 ~error:None
465 ~exit_code:None
466 ~mode:env.Env.mode
467 ~file:(text_source_to_filename env.Env.text_source)
468 ~root:env.Env.root;
469 with exn ->
470 let exit_code = get_exception_exit_value exn in
471 if exit_code = 255 then Printexc.print_backtrace stderr;
472 let err_str = get_error_string_from_exn exn in
473 let msg = match exn with
474 | InvalidSyntax ->
475 err_str
476 | InvalidCliArg s
477 | InvalidDiff s ->
478 err_str ^ ": " ^ s
479 | _ ->
480 err_str ^ ": " ^ (Printexc.to_string exn)
482 let time_taken = Unix.gettimeofday () -. start_time in
483 if not env.Env.test then
484 Logger.exit
485 ~time_taken
486 ~error:(Some msg)
487 ~exit_code:(Some exit_code)
488 ~mode:env.Env.mode
489 ~file:(text_source_to_filename env.Env.text_source)
490 ~root:env.Env.root;
491 eprintf "%s\n" msg;
492 exit exit_code