Refactor main

- Configuration options
- Option error detection
- Dedicated output types
- Printers
This commit is contained in:
Rijnard van Tonder 2019-05-29 22:06:29 -04:00 committed by GitHub
parent 53f91888eb
commit eabf75d7a7
No known key found for this signature in database
GPG Key ID: 4AEE18F83AFDEB23
26 changed files with 1074 additions and 394 deletions

View File

@ -1,5 +1,6 @@
module Language = Language
module Matchers = Matchers
module Match = Match
module Replacement = Replacement
module Rewriter = Rewriter
module Statistics = Statistics

View File

@ -1,5 +1,6 @@
module Language = Language
module Matchers = Matchers
module Match = Match
module Replacement = Replacement
module Rewriter = Rewriter
module Statistics = Statistics

View File

@ -8,6 +8,7 @@
mparser
mparser.pcre
comby.matchers
comby.replacement
comby.rewriter
comby.match
comby.language

View File

@ -65,3 +65,9 @@ type t =
[@@deriving yojson]
val create : unit -> t
val pp_json_pretty : Format.formatter -> string option * t list -> unit
val pp_json_lines : Format.formatter -> string option * t list -> unit
val pp_match_result : Format.formatter -> string option * t list -> unit

View File

@ -1,3 +1,5 @@
open Core
type t =
{ range : Range.t
; environment : Environment.t
@ -10,3 +12,40 @@ let create () =
; environment = Environment.create ()
; matched = ""
}
let to_json source_path matches =
let json_matches matches = `List (List.map ~f:to_yojson matches) in
let uri =
match source_path with
| Some path -> `String path
| None -> `Null
in
`Assoc
[ ("uri", uri)
; ("matches", json_matches matches)
]
let yojson_to_string kind json =
match kind with
| `Pretty -> Yojson.Safe.pretty_to_string json
| `Lines -> Yojson.Safe.to_string json
let pp_json_pretty ppf (source_path, matches) =
Format.fprintf ppf "%s" @@ yojson_to_string `Pretty @@ to_json source_path matches
let pp_json_lines ppf (source_path, matches) =
Format.fprintf ppf "%s" @@ yojson_to_string `Lines @@ to_json source_path matches
let pp_match_result ppf (source_path, matches) =
let pp_source_path ppf source_path =
match source_path with
| Some path -> Format.fprintf ppf " in %s " path
| None -> Format.fprintf ppf "%s" " "
in
(* FIXME *)
let spec_number = 0 in
Format.fprintf ppf
"%d matches%afor spec %d (use -json-pretty for json format)\n"
(List.length matches)
pp_source_path source_path
(spec_number + 1)

View File

@ -348,3 +348,30 @@ module C_nested_comments = struct
include Matcher.Make(Syntax)
end
let select_with_extension extension : (module Types.Matcher.S) =
match extension with
| ".c" | ".h" | ".cc" | ".cpp" | ".hpp" -> (module C)
| ".clj" -> (module Clojure)
| ".css" -> (module CSS)
| ".dart" -> (module Dart)
| ".elm" -> (module Elm)
| ".erl" -> (module Erlang)
| ".ex" -> (module Elixir)
| ".html" | ".xml" -> (module Html)
| ".hs" -> (module Haskell)
| ".go" -> (module Go)
| ".java" -> (module Java)
| ".js" | ".ts" -> (module Javascript)
| ".ml" | ".mli" -> (module OCaml)
| ".php" -> (module Php)
| ".py" -> (module Python)
| ".rb" -> (module Ruby)
| ".rs" -> (module Rust)
| ".s" | ".asm" -> (module Assembly)
| ".scala" -> (module Scala)
| ".sql" -> (module SQL)
| ".sh" -> (module Bash)
| ".swift" -> (module Swift)
| ".tex" | ".bib" -> (module Latex)
| _ -> (module Generic)

View File

@ -1,5 +1,4 @@
include Languages
module Configuration = Configuration
module type Matcher = Types.Matcher.S
include Languages

View File

@ -1,5 +1,4 @@
include module type of Languages
module Configuration = Configuration
module type Matcher = Types.Matcher.S
include module type of Languages

5
lib/replacement/dune Normal file
View File

@ -0,0 +1,5 @@
(library
(name replacement)
(public_name comby.replacement)
(preprocess (pps ppx_deriving.show ppx_deriving.eq ppx_sexp_conv ppx_sexp_message ppx_deriving_yojson bisect_ppx -conditional -no-comment-parsing))
(libraries comby.parsers comby.match ppxlib core mparser mparser.pcre yojson ppx_deriving_yojson ppx_deriving_yojson.runtime patdiff.lib))

View File

@ -0,0 +1,77 @@
open Core
open Match
type t =
{ range : range
; replacement_content : string
; environment : environment
}
[@@deriving yojson]
type result =
{ rewritten_source : string
; in_place_substitutions : t list
}
[@@deriving yojson]
let empty_result =
{ rewritten_source = ""
; in_place_substitutions = []
}
[@@deriving yojson]
let to_json replacements path diff result =
let value = `List (List.map ~f:to_yojson replacements) in
let uri =
match path with
| Some path -> `String path
| None -> `Null
in
let diff =
match diff with
| Some diff -> `String diff
| None -> `Null
in
`Assoc
[ ("uri", uri)
; ("rewritten_source", `String result)
; ("in_place_substitutions", value)
; ("diff", diff)
]
let get_diff source_path source_content result =
let open Patdiff_lib in
let source_path =
match source_path with
| Some path -> path
| None -> "/dev/null"
in
let configuration = Diff_configuration.plain () in
let prev = Patdiff_core.{ name = source_path; text = source_content } in
let next = Patdiff_core.{ name = source_path; text = result } in
Compare_core.diff_strings
~print_global_header:true
configuration
~prev
~next
|> function
| `Different diff -> Some diff
| `Same -> None
let yojson_to_string kind json =
match kind with
| `Pretty -> Yojson.Safe.pretty_to_string json
| `Lines -> Yojson.Safe.to_string json
let pp_json_pretty ppf (source_path, source_content, replacements, replacement_content) =
let diff = get_diff source_path source_content replacement_content in
Format.fprintf ppf "%s" @@ yojson_to_string `Pretty @@ to_json replacements source_path diff replacement_content
let pp_json_lines ppf (source_path, source_content, replacements, replacement_content) =
let diff = get_diff source_path source_content replacement_content in
Format.fprintf ppf "%s" @@ Yojson.Safe.to_string @@ to_json replacements source_path diff replacement_content
let pp_diff ppf (source_path, source_content, replacement_content) =
let diff = get_diff source_path source_content replacement_content in
Option.value_map diff ~default:() ~f:(fun diff -> Format.fprintf ppf "%s@." diff)

View File

@ -0,0 +1,22 @@
open Match
type t =
{ range : range
; replacement_content : string
; environment : environment
}
[@@deriving yojson]
type result =
{ rewritten_source : string
; in_place_substitutions : t list
}
[@@deriving yojson]
val empty_result : result
val pp_json_pretty : Format.formatter -> string option * string * t list * string -> unit
val pp_json_lines : Format.formatter -> string option * string * t list * string -> unit
val pp_diff : Format.formatter -> string option * string * string -> unit

View File

@ -2,4 +2,4 @@
(name rewriter)
(public_name comby.rewriter)
(preprocess (pps ppx_deriving.show ppx_sexp_conv ppx_deriving_yojson bisect_ppx -conditional -no-comment-parsing))
(libraries comby.matchers ppxlib core core.uuid))
(libraries comby.matchers comby.replacement ppxlib core core.uuid))

View File

@ -1,33 +1,14 @@
open Core
open Match
type match_context_replacement =
{ range : range
; replacement_content : string
; environment : environment
}
[@@deriving yojson]
type result =
{ rewritten_source : string
; in_place_substitutions : match_context_replacement list
}
[@@deriving yojson]
let empty_result =
{ rewritten_source = ""
; in_place_substitutions = []
}
[@@deriving yojson]
open Replacement
let substitute_match_contexts (matches: Match.t list) source replacements =
let rewrite_template, environment =
List.fold2_exn
matches replacements
~init:(source, Environment.create ())
~f:(fun
(rewrite_template, accumulator_environment)
~f:(fun (rewrite_template, accumulator_environment)
({ environment = _match_environment; _ } as match_)
{ replacement_content; _ } ->
(* create a hole in the rewrite template based on this match context *)

View File

@ -1,22 +1,7 @@
open Match
type match_context_replacement =
{ range : range
; replacement_content : string
; environment : environment
}
[@@deriving yojson]
type result =
{ rewritten_source : string
; in_place_substitutions : match_context_replacement list
}
[@@deriving yojson]
(** if [source] is given, substitute in-place. If not,
emit result separated by newlines *)
val all
: ?source:string
-> rewrite_template:string
-> Match.t list
-> result option
-> Replacement.result option

2
lib/rewriter/rewriter.ml Normal file
View File

@ -0,0 +1,2 @@
module Rewrite = Rewrite
module Rewrite_template = Rewrite_template

View File

@ -0,0 +1,2 @@
module Rewrite = Rewrite
module Rewrite_template = Rewrite_template

View File

@ -0,0 +1,360 @@
open Core
open Language
let read = Fn.compose String.rstrip In_channel.read_all
let read_template =
Fn.compose
String.chop_suffix_exn ~suffix:"\n"
In_channel.read_all
let parse_specification_directories match_only specification_directory_paths =
let parse_directory path =
let match_template =
let filename = path ^/ "match" in
try read_template filename
with _ -> failwith (Format.sprintf "Could not read required match file %s" filename)
in
let match_rule =
let filename = path ^/ "match_rule" in
try Some (read filename)
with _ -> None
in
let rewrite_template =
let filename = path ^/ "rewrite" in
if match_only then
None
else
try Some (read_template filename)
with _ -> None
in
let rewrite_rule =
let filename = path ^/ "rewrite_rule" in
if match_only then
None
else
try Some (read filename)
with _ -> None
in
Specification.create ~match_template ?match_rule ?rewrite_template ?rewrite_rule ()
in
List.map specification_directory_paths ~f:parse_directory
let parse_source_directories ?(file_extensions = []) target_directory =
let rec ls_rec path =
if Sys.is_file path = `Yes then
match file_extensions with
| [] -> [path]
| suffixes when List.exists suffixes ~f:(fun suffix -> String.is_suffix ~suffix path) -> [path]
| _ -> []
else
try
Sys.ls_dir path
|> List.map ~f:(fun sub -> ls_rec (Filename.concat path sub))
|> List.concat
with
| _ -> []
in
ls_rec target_directory
type output_options =
{ json_pretty : bool
; json_lines : bool
; in_place : bool
; stdin : bool
; output_diff : bool
}
type user_input_options =
{ rule : string
; specification_directories : string list option
; anonymous_arguments : (string * string * string list list option) option
; file_extensions : string list option
; zip_file : string option
; match_only : bool
; target_directory : string
}
type run_options =
{ sequential : bool
; verbose : bool
; match_timeout : int
; number_of_workers : int
; dump_statistics : bool
}
type user_input =
{ input_options : user_input_options
; run_options : run_options
; output_options : output_options
}
module Printer = struct
type printable_result =
| Matches of
{ source_path : string option
; matches : Match.t list
}
| Replacements of
{ source_path : string option
; replacements : Replacement.t list
; result : string
; source_content : string
}
type t = printable_result -> unit
module Match : sig
type match_output =
| Json_lines
| Json_pretty
| Diff
| Number_of_matches
val convert : output_options -> match_output
val print : match_output -> string option -> Match.t list -> unit
end = struct
type match_output =
| Json_lines
| Json_pretty
| Diff
| Number_of_matches
let convert output_options =
match output_options with
| { json_pretty = true; json_lines = true; _ }
| { json_pretty = true; json_lines = false; _ } -> Json_pretty
| { json_pretty = false; json_lines = true; _ } -> Json_lines
| _ -> Number_of_matches
let print (match_output : match_output) source_path matches =
let ppf = Format.std_formatter in
match match_output with
| Json_lines -> Format.fprintf ppf "%a" Match.pp_json_lines (source_path, matches)
| Json_pretty -> Format.fprintf ppf "%a" Match.pp_json_pretty (source_path, matches)
| Number_of_matches -> Format.fprintf ppf "%a" Match.pp_match_result (source_path, matches)
| Diff -> assert false
end
module Rewrite : sig
type replacement_output =
| In_place
| Stdout
| Json_lines
| Json_pretty
| Diff
val convert : output_options -> replacement_output
val print : replacement_output -> string option -> Replacement.t list -> string -> string -> unit
end = struct
type replacement_output =
| In_place
| Stdout
| Json_lines
| Json_pretty
| Diff
let convert output_options : replacement_output =
match output_options with
| { json_pretty = false; json_lines = false; stdin = false; in_place = true; _ } -> In_place
| { json_pretty = false; json_lines = false; stdin = false; in_place = false; _ } -> Stdout
| { json_pretty = true; in_place = false; _ } -> Json_pretty
| { json_lines = true; in_place = false; _ } -> Json_lines
| { output_diff = true; _ } -> Diff
| _ -> Stdout
let print replacement_output path replacements replacement_content source_content =
let ppf = Format.std_formatter in
match path, replacement_output with
| Some path, In_place -> Out_channel.write_all path ~data:replacement_content
| _, Stdout -> Format.fprintf ppf "%s" replacement_content
| Some path, Json_pretty ->
Format.fprintf ppf "%a" Replacement.pp_json_pretty (Some path, source_content, replacements, replacement_content)
| Some path, Json_lines -> Format.fprintf ppf "%a" Replacement.pp_json_lines (Some path, source_content, replacements, replacement_content)
| None, Json_pretty -> Format.fprintf ppf "%a" Replacement.pp_json_pretty (path, source_content, replacements, replacement_content)
| None, Json_lines -> Format.fprintf ppf "%a" Replacement.pp_json_lines (path, source_content, replacements, replacement_content)
| Some in_, Diff -> Format.fprintf ppf "%a" Replacement.pp_diff (Some in_, source_content, replacement_content)
| None, _ -> Format.printf "%s" replacement_content
end
end
type t =
{ sources : Command_input.t
; specifications : Specification.t list
; file_extensions : string list option
; run_options : run_options
; output_printer : Printer.t
}
let validate_errors
{ input_options =
{ rule
; specification_directories
; anonymous_arguments
; zip_file
; _
}
; run_options = _
; output_options =
{
in_place;
stdin;
_
}
} =
let violations =
[ stdin && Option.is_some zip_file
, "-zip may not be used with stdin."
; stdin && in_place
, "-i may not be used with stdin."
; anonymous_arguments = None &&
(specification_directories = None
|| specification_directories = Some []),
"No templates specified. \
Either on the command line, or \
using -templates \
<directory-containing-templates>"
; let result = Rule.create rule in
Or_error.is_error result,
if Or_error.is_error result then
Format.sprintf "Match rule parse error: %s@." @@
Error.to_string_hum (Option.value_exn (Result.error result))
else
"UNREACHABLE"
;
]
in
List.filter_map violations ~f:(function
| true, message -> Some (Or_error.error_string message)
| _ -> None)
|> Or_error.combine_errors_unit
|> Result.map_error ~f:(fun error ->
let message =
let rec to_string acc =
function
| Sexp.Atom s -> s
| List [] -> ""
| List (x::[]) -> to_string acc x
| List (x::xs) ->
(List.fold xs ~init:acc ~f:to_string) ^ "\nNext error: " ^ to_string acc x
in
Error.to_string_hum error
|> Sexp.of_string
|> to_string ""
in
Error.of_string message)
let emit_warnings { input_options; output_options; _ } =
let warn_on =
[ is_some input_options.specification_directories
&& is_some input_options.anonymous_arguments,
"Templates specified on the command line AND using -templates. Ignoring match
and rewrite templates on the command line and only using those in directories."
; output_options.json_lines = true && output_options.json_pretty = true,
"Both -json-lines and -json-pretty specified. Using -json-pretty."
]
in
List.iter warn_on ~f:(function
| true, message -> Format.eprintf "Warning: %s@." message
| _ -> ());
Ok ()
let create
({ input_options =
{ rule
; specification_directories
; anonymous_arguments
; file_extensions
; zip_file
; match_only
; target_directory
}
; run_options =
{ sequential
; verbose
; match_timeout
; number_of_workers
; dump_statistics
}
; output_options =
({
in_place;
stdin;
_
} as output_options)
} as configuration)
: t Or_error.t =
let open Or_error in
validate_errors configuration >>= fun () ->
emit_warnings configuration >>= fun () ->
let specifications =
match specification_directories, anonymous_arguments with
| None, Some (match_template, rewrite_template, _) ->
if match_only then
[Specification.create ~match_template ~match_rule:rule ()]
else
[Specification.create ~match_template ~rewrite_template ~match_rule:rule ~rewrite_rule:rule ()]
| Some specification_directories, _ ->
parse_specification_directories match_only specification_directories
| _ -> assert false
in
let stdin, file_extensions =
(* Really activate stdin mode if not in the 3rd anonymous arg?
Is the 3rd arnonymous arg meant to case out on a matcher kind, filter, or
control stdin activation? *)
match anonymous_arguments with
| Some (_, _, None) -> true, file_extensions
| Some (_, _, Some file_extensions) -> false, (Some (List.concat file_extensions))
(* No anonymous arguments: if -stdin was specified, this lets
-templates work with stdin. *)
| None -> stdin, file_extensions
in
let sources =
match stdin, zip_file with
| true, _ ->
`String (In_channel.input_all In_channel.stdin)
| _, Some zip_file ->
`Zip zip_file
(* Recurse in directories *)
| false, None ->
`Paths (parse_source_directories ?file_extensions target_directory)
in
let in_place = if is_some zip_file then false else in_place in
let output_options = { output_options with in_place } in
let output_printer printable =
let open Printer in
match printable with
| Matches { source_path; matches } ->
Printer.Match.convert output_options
|> fun match_output ->
Printer.Match.print match_output source_path matches
| Replacements { source_path; replacements; result; source_content } ->
Printer.Rewrite.convert output_options
|> fun replacement_output ->
Printer.Rewrite.print replacement_output source_path replacements result source_content
in
return
{ sources
; specifications
; file_extensions
; run_options =
{ sequential
; verbose
; match_timeout
; number_of_workers
; dump_statistics
}
; output_printer
}

View File

@ -0,0 +1,59 @@
open Core
module Printer : sig
type printable_result =
| Matches of
{ source_path : string option
; matches : Match.t list
}
| Replacements of
{ source_path : string option
; replacements : Replacement.t list
; result : string
; source_content : string
}
type t = printable_result -> unit
end
type output_options =
{ json_pretty : bool
; json_lines : bool
; in_place : bool
; stdin : bool
; output_diff : bool
}
type user_input_options =
{ rule : string
; specification_directories : string list option
; anonymous_arguments : (string * string * string list list option) option
; file_extensions : string list option
; zip_file : string option
; match_only : bool
; target_directory : string
}
type run_options =
{ sequential : bool
; verbose : bool
; match_timeout : int
; number_of_workers : int
; dump_statistics : bool
}
type user_input =
{ input_options : user_input_options
; run_options : run_options
; output_options : output_options
}
type t =
{ sources : Command_input.t
; specifications : Specification.t list
; file_extensions : string list option
; run_options : run_options
; output_printer : Printer.t
}
val create : user_input -> t Or_error.t

17
src/command_input.ml Normal file
View File

@ -0,0 +1,17 @@
type single_input_kind =
[ `String of string
| `Path of string
]
type t =
[ `Paths of string list
| `Zip of string
| single_input_kind
]
let show_input_kind =
function
| `Paths _ -> Format.sprintf "Paths..."
| `Path path -> Format.sprintf "Path: %s" path
| `String s -> Format.sprintf "String: %s" s
| `Zip _ -> Format.sprintf "Zip..."

View File

@ -1,7 +1,7 @@
(executables
(libraries comby core ppx_deriving_yojson ppx_deriving_yojson.runtime hack_parallel camlzip patdiff.lib)
(preprocess (pps ppx_deriving_yojson ppx_let ppx_deriving.show))
(modules main specification diff_configuration)
(modules main specification command_configuration command_input)
(names main))
(executables

View File

@ -3,6 +3,8 @@ open Command.Let_syntax
open Hack_parallel
open Command_configuration
open Command_input
open Matchers
open Match
open Language
@ -15,31 +17,11 @@ type json_result =
}
[@@deriving yojson]
type input_kind =
| Paths of string list
| Path of string
| String of string
| Zip of string
let show_input_kind (i : input_kind) =
match i with
| Paths _ -> Format.sprintf "Paths..."
| Path path -> Format.sprintf "Path: %s" path
| String s -> Format.sprintf "String: %s" s
| Zip _ -> Format.sprintf "Zip..."
type processed_source_result =
| Matches of (Match.t list * int)
| Rewritten of (Rewrite.match_context_replacement list * string * int)
| Replacement of (Replacement.t list * string * int)
| Nothing
let read = Fn.compose String.rstrip In_channel.read_all
let read_template =
Fn.compose
String.chop_suffix_exn ~suffix:"\n"
In_channel.read_all
let verbose_out_file = "/tmp/comby.out"
let get_matches (module Matcher : Matchers.Matcher) configuration match_template match_rule source =
@ -65,18 +47,23 @@ let apply_rewrite_rule matcher rewrite_rule matches =
let rewrite rewrite_template _rewrite_rule source matches =
Rewrite.all ~source ~rewrite_template matches
let process_single_source matcher verbose configuration source specification match_timeout =
let process_single_source
matcher
match_configuration
source
specification
verbose
match_timeout =
let open Specification in
try
let input_text =
match source with
| String input_text -> input_text
| Path path ->
| `String input_text -> input_text
| `Path path ->
if verbose then
Out_channel.with_file ~append:true verbose_out_file ~f:(fun out_channel ->
Out_channel.output_lines out_channel [Format.sprintf "Processing %s%!" path]);
In_channel.read_all path
| _ -> failwith "Don't send multiple paths to process_single_source"
in
match specification with
| { match_specification = { match_template; match_rule }
@ -84,7 +71,7 @@ let process_single_source matcher verbose configuration source specification mat
} ->
let matches =
try
let f () = get_matches matcher configuration match_template match_rule input_text in
let f () = get_matches matcher match_configuration match_template match_rule input_text in
Statistics.Time.time_out ~after:match_timeout f ();
with Statistics.Time.Time_out ->
Format.eprintf "Timeout for input: %s!@." (show_input_kind source);
@ -99,14 +86,14 @@ let process_single_source matcher verbose configuration source specification mat
let result =
try
let f () =
get_matches matcher configuration match_template match_rule input_text
get_matches matcher match_configuration match_template match_rule input_text
|> fun matches ->
(* TODO(RVT): merge match and rewrite rule application. *)
apply_rewrite_rule matcher rewrite_rule matches
|> fun matches ->
if matches = [] then
(* If there are no matches, return the original source (for editor support). *)
Some (Some (Rewrite.{ rewritten_source = input_text; in_place_substitutions = [] }), [])
Some (Some (Replacement.{ rewritten_source = input_text; in_place_substitutions = [] }), [])
else
Some (rewrite rewrite_template rewrite_rule input_text matches, matches)
in
@ -120,122 +107,26 @@ let process_single_source matcher verbose configuration source specification mat
result
|> function
| Some (Some { rewritten_source; in_place_substitutions }, matches) ->
Rewritten (in_place_substitutions, rewritten_source, List.length matches)
Replacement (in_place_substitutions, rewritten_source, List.length matches)
| Some (None, _)
| None -> Nothing
with
| _ ->
Nothing
let output_result stdin spec_number json_pretty json_lines output_diff source_path source_content result in_place =
let source_content =
match source_content with
| String content -> content
| Path path -> In_channel.read_all path
| _ -> failwith "This cannot be a zip or paths"
in
let output_result output_printer source_path source_content result =
match result with
| Nothing -> ()
| Matches (matches, _) ->
if json_pretty || json_lines then
let json_matches = `List (List.map ~f:Match.to_yojson matches) in
let json =
match source_path with
| None -> `Assoc [("uri", `Null); ("matches", json_matches)]
| Some path -> `Assoc [("uri", `String path); ("matches", json_matches)]
in
if json_lines then
Format.printf "%s@." @@ Yojson.Safe.to_string json
else
Format.printf "%s%!" @@ Yojson.Safe.pretty_to_string json
else
let with_file =
match source_path with
| Some path -> Format.sprintf " in %s " path
| None -> " "
in
Format.printf
"%d matches%sfor spec %d (use -json-pretty for json format)@."
(List.length matches)
with_file
(spec_number + 1)
| Rewritten (replacements, result, _) ->
match source_path, json_pretty, json_lines, stdin, in_place with
(* rewrite in place *)
| Some path, false, false, false, true -> Out_channel.write_all path ~data:result
(* stdin, not JSON *)
| _, false, false, true, false -> Format.printf "%s%!" result
(* JSON with path *)
| Some path, true, _, _, false
| Some path, _, true, _, false ->
let diff =
let open Patdiff_lib in
(* FIXME(RVT) don't reread the file here *)
let configuration = Diff_configuration.plain () in
let from_ = Patdiff_core.{ name = path; text = source_content } in
let to_ = Patdiff_core.{ name = path; text = result } in
Compare_core.diff_strings
~print_global_header:true
configuration
~prev:from_
~next:to_
|> function
| `Different diff -> Some diff
| `Same -> None
in
begin match diff with
| Some diff ->
let json_rewrites =
let value =
`List (List.map ~f:Rewrite.match_context_replacement_to_yojson replacements) in
`Assoc
[ ("uri", `String path)
; ("rewritten_source", `String result)
; ("in_place_substitutions", value)
; ("diff", `String diff)
]
in
if json_lines then
Format.printf "%s@." @@ Yojson.Safe.to_string json_rewrites
else
Format.printf "%s%!" @@ Yojson.Safe.pretty_to_string json_rewrites
| None -> ()
end
(* stdin, JSON, no path *)
| None, true, _, _, false
| None, _, true, _, false ->
let json_rewrites =
let value = `List (List.map ~f:Rewrite.match_context_replacement_to_yojson replacements) in
`Assoc [("uri", `Null); ("rewritten_source", `String result); ("in_place_substitutions", value)]
in
if json_lines then
Format.printf "%s@." @@ Yojson.Safe.to_string json_rewrites
else
Format.printf "%s%!" @@ Yojson.Safe.pretty_to_string json_rewrites
(* stdout for everything else *)
| in_, _, _, _, _ ->
if not output_diff || Option.is_none in_ then
Format.printf "%s%!" result
else
let diff =
let open Patdiff_lib in
(* FIXME(RVT) don't reread the file here *)
let configuration = Diff_configuration.terminal () in
let path = Option.value_exn in_ in
let from_ = Patdiff_core.{ name = path; text = source_content } in
let to_ = Patdiff_core.{ name = path; text = result } in
Compare_core.diff_strings
~print_global_header:true
configuration
~prev:from_
~next:to_
|> function
| `Different diff -> Some diff
| `Same -> None
in
match diff with
| Some result -> Format.printf "%s@." result
| None -> ()
output_printer (Printer.Matches { source_path; matches })
| Replacement (replacements, result, _) ->
let source_content =
match source_content with
| `String content -> content
| `Path path -> In_channel.read_all path
in
output_printer (Printer.Replacements { source_path; replacements; result; source_content })
let write_statistics number_of_matches paths total_time dump_statistics =
if dump_statistics then
@ -271,28 +162,24 @@ let paths_with_file_size paths =
in
(path, length))
(** If users give e.g., *.c, convert it to .c *)
let fake_glob_file_extensions file_extensions =
List.map file_extensions ~f:(String.substr_replace_all ~pattern:"*" ~with_:"")
let run
matcher
(sources : input_kind)
(specifications : Specification.t list)
sequential
number_of_workers
stdin
json_pretty
json_lines
output_diff
verbose
match_timeout
in_place
dump_statistics
file_extensions =
{ sources
; specifications
; file_extensions
; run_options =
{ sequential
; verbose
; match_timeout
; number_of_workers
; dump_statistics
}
; output_printer
}
=
let number_of_workers = if sequential then 0 else number_of_workers in
let scheduler = Scheduler.create ~number_of_workers () in
let configuration = Configuration.create ~match_kind:Fuzzy () in
let match_configuration = Configuration.create ~match_kind:Fuzzy () in
let total_time = Statistics.Time.start () in
let run_on_specifications input output_file =
@ -301,31 +188,31 @@ let run
let input =
match result with
| Nothing | Matches _ -> input
| Rewritten (_, content, _) -> String content
| Replacement (_, content, _) -> `String content
in
process_single_source matcher verbose configuration input specification match_timeout
process_single_source matcher match_configuration input specification verbose match_timeout
|> function
| Nothing -> Nothing, count
| Matches (x, number_of_matches) ->
Matches (x, number_of_matches), count + number_of_matches
| Rewritten (x, content, number_of_matches) ->
Rewritten (x, content, number_of_matches),
| Replacement (x, content, number_of_matches) ->
Replacement (x, content, number_of_matches),
count + number_of_matches)
in
output_result stdin 0 json_pretty json_lines output_diff output_file input result in_place;
output_result output_printer output_file input result;
count
in
match sources with
| String source ->
let number_of_matches = run_on_specifications (String source) None in
| `String source ->
let number_of_matches = run_on_specifications (`String source) None in
(* FIXME(RVT): statistics for single source text doesn't output LOC *)
write_statistics number_of_matches [] total_time dump_statistics
| Paths paths ->
| `Paths paths ->
if sequential then
let number_of_matches =
List.fold ~init:0 paths ~f:(fun acc path ->
let matches = run_on_specifications (Path path) (Some path) in
let matches = run_on_specifications (`Path path) (Some path) in
acc + matches)
in
write_statistics number_of_matches paths total_time dump_statistics
@ -334,7 +221,7 @@ let run
List.fold
paths
~init
~f:(fun count path -> count + run_on_specifications (Path path) (Some path))
~f:(fun count path -> count + run_on_specifications (`Path path) (Some path))
in
let number_of_matches =
try Scheduler.map_reduce scheduler ~init:0 ~map ~reduce:(+) paths
@ -347,21 +234,20 @@ let run
()
end;
write_statistics number_of_matches paths total_time dump_statistics
| Zip zip_file ->
| `Zip zip_file ->
if sequential then
let zip_in = Zip.open_in zip_file in
let entries =
match file_extensions with
| Some [] | None -> List.filter (Zip.entries zip_in) ~f:(fun { is_directory; _ } -> not is_directory)
| Some suffixes ->
let suffixes = fake_glob_file_extensions suffixes in
List.filter (Zip.entries zip_in) ~f:(fun { is_directory; filename; _ } ->
not is_directory && List.exists suffixes ~f:(fun suffix -> String.is_suffix ~suffix filename))
in
let number_of_matches =
List.fold ~init:0 entries ~f:(fun acc ({ filename; _ } as entry) ->
let source = Zip.read_entry zip_in entry in
let matches = run_on_specifications (String source) (Some filename) in
let matches = run_on_specifications (`String source) (Some filename) in
acc + matches)
in
Zip.close_in zip_in;
@ -375,7 +261,7 @@ let run
~init
~f:(fun count ({ filename; _ } as entry) ->
let source = Zip.read_entry zip_in entry in
let matches = run_on_specifications (String source) (Some filename) in
let matches = run_on_specifications (`String source) (Some filename) in
count + matches)
in
Zip.close_in zip_in;
@ -387,7 +273,6 @@ let run
match file_extensions with
| Some [] | None -> List.filter (Zip.entries zip_in) ~f:(fun { is_directory; _ } -> not is_directory)
| Some suffixes ->
let suffixes = fake_glob_file_extensions suffixes in
List.filter (Zip.entries zip_in) ~f:(fun { is_directory; filename; _ } ->
not is_directory && List.exists suffixes ~f:(fun suffix -> String.is_suffix ~suffix filename))
in
@ -404,56 +289,6 @@ let run
write_statistics number_of_matches [] total_time dump_statistics
| _ -> failwith "No single path handled here"
let parse_source_directories ?(file_extensions = []) target_directory =
let rec ls_rec path =
if Sys.is_file path = `Yes then
match file_extensions with
| [] -> [path]
| suffixes when List.exists suffixes ~f:(fun suffix -> String.is_suffix ~suffix path) ->
[path]
| _ -> []
else
try
Sys.ls_dir path
|> List.map ~f:(fun sub -> ls_rec (Filename.concat path sub))
|> List.concat
with
| _ -> []
in
ls_rec target_directory
let parse_specification_directories match_only specification_directory_paths =
let parse_directory path =
let match_template =
let filename = path ^/ "match" in
try read_template filename
with _ -> failwith (Format.sprintf "Could not read required match file %s" filename)
in
let match_rule =
let filename = path ^/ "match_rule" in
try Some (read filename)
with _ -> None
in
let rewrite_template =
let filename = path ^/ "rewrite" in
if match_only then
None
else
try Some (read_template filename)
with _ -> None
in
let rewrite_rule =
let filename = path ^/ "rewrite_rule" in
if match_only then
None
else
try Some (read filename)
with _ -> None
in
Specification.create ~match_template ?match_rule ?rewrite_template ?rewrite_rule ()
in
List.map specification_directory_paths ~f:parse_directory
let base_command_parameters : (unit -> 'result) Command.Param.t =
[%map_open
(* flags. *)
@ -464,7 +299,7 @@ let base_command_parameters : (unit -> 'result) Command.Param.t =
and match_timeout = flag "timeout" (optional_with_default 3 int) ~doc:"seconds Set match timeout on a source. Default: 3 seconds"
and target_directory = flag "directory" ~aliases:["d"; "recursive"] (optional_with_default "." string) ~doc:(Format.sprintf "path Run recursively on files in a directory. Default is current directory: %s" @@ Sys.getcwd ())
and specification_directories = flag "templates" (optional (Arg_type.comma_separated string)) ~doc:"path CSV of directories containing templates"
and file_extensions = flag "extensions" ~aliases:["e"; "file-extensions"; "f"] (optional (Arg_type.comma_separated string)) ~doc:"extensions CSV of extensions to include, like \".go\" or \".c,.h\""
and file_extensions = flag "extensions" ~aliases:["e"; "file-extensions"; "f"] (optional (Arg_type.comma_separated string)) ~doc:"extensions Comma-separated extensions to include, like \".go\" or \".c,.h\". It is just a file suffix, so you can use it to match whole file names like \"main.go\""
and zip_file = flag "zip" ~aliases:["z"] (optional string) ~doc:"zipfile A zip file containing files to rewrite"
and json_pretty = flag "json-pretty" no_arg ~doc:"Output pretty JSON format"
and json_lines = flag "json-lines" no_arg ~doc:"Output JSON line format"
@ -483,94 +318,45 @@ let base_command_parameters : (unit -> 'result) Command.Param.t =
)
)
in
let configuration =
Command_configuration.create
{ input_options =
{ rule
; specification_directories
; anonymous_arguments
; file_extensions
; zip_file
; match_only
; target_directory
}
; run_options =
{ sequential
; verbose
; match_timeout
; number_of_workers
; dump_statistics
}
; output_options =
{ json_pretty
; json_lines
; in_place
; stdin
; output_diff
}
}
|> function
| Ok configuration -> configuration
| Error error ->
Format.eprintf "%s@." @@ Error.to_string_hum error;
exit 1
in
fun () ->
let () =
match Rule.create rule with
| Ok _ -> ()
| Error error ->
let message = Error.to_string_hum error in
Format.printf "Match rule parse error: %s@." message;
exit 1
in
let specifications =
match specification_directories, anonymous_arguments with
| None, None
| Some [], None ->
Format.eprintf
"Please specify templates. Either on the command line, or using \
-templates [dir]@.";
exit 1
| None, Some (match_template, rewrite_template, _) ->
if match_only then
[Specification.create ~match_template ~match_rule:rule ()]
else
[Specification.create ~match_template ~rewrite_template ~match_rule:rule ~rewrite_rule:rule ()]
| Some specification_directories, None ->
parse_specification_directories match_only specification_directories
| Some specification_directories, Some _ ->
Format.eprintf
"Warning: ignoring match and rewrite templates and rules on \
commandline and using those in directories instead@.";
parse_specification_directories match_only specification_directories
in
let stdin, file_extensions =
match anonymous_arguments with
| Some (_, _, None) -> true, file_extensions
| Some (_, _, Some file_extensions) -> false, (Some (List.concat file_extensions))
(* No anonymous arguments: if -stdin was specified, this lets
-templates work with stdin. *)
| None -> stdin, file_extensions
in
if stdin && (Option.is_some zip_file) then
(Format.eprintf "-zip may not be used with stdin";
exit 1)
else if stdin && in_place then
(Format.eprintf "-i may not be used with stdin";
exit 1);
let sources =
match stdin, zip_file with
| true, _ ->
String (In_channel.input_all In_channel.stdin)
| _, Some zip_file ->
Zip zip_file
(* Recurse in directories *)
| false, None ->
let file_extensions = Option.map file_extensions ~f:fake_glob_file_extensions in
Paths (parse_source_directories ?file_extensions target_directory)
in
let (module M : Matchers.Matcher) =
let matcher =
match file_extensions with
| None | Some [] -> (module Matchers.Generic)
| Some (hd::_) ->
match hd with
| ".c" | ".h" | ".cc" | ".cpp" | ".hpp" -> (module Matchers.C)
| ".clj" -> (module Matchers.Clojure)
| ".css" -> (module Matchers.CSS)
| ".dart" -> (module Matchers.Dart)
| ".elm" -> (module Matchers.Elm)
| ".erl" -> (module Matchers.Erlang)
| ".ex" -> (module Matchers.Elixir)
| ".html" | ".xml" -> (module Matchers.Html)
| ".hs" -> (module Matchers.Haskell)
| ".go" -> (module Matchers.Go)
| ".java" -> (module Matchers.Java)
| ".js" | ".ts" -> (module Matchers.Javascript)
| ".ml" | ".mli" -> (module Matchers.OCaml)
| ".php" -> (module Matchers.Php)
| ".py" -> (module Matchers.Python)
| ".rb" -> (module Matchers.Ruby)
| ".rs" -> (module Matchers.Rust)
| ".s" | ".asm" -> (module Matchers.Assembly)
| ".scala" -> (module Matchers.Scala)
| ".sql" -> (module Matchers.SQL)
| ".sh" -> (module Matchers.Bash)
| ".swift" -> (module Matchers.Swift)
| ".tex" | ".bib" -> (module Matchers.Latex)
| _ -> (module Matchers.Generic)
| None | Some [] -> Matchers.select_with_extension ".generic"
| Some (extension::_) -> Matchers.select_with_extension extension
in
let in_place = if is_some zip_file then false else in_place in
run (module M) sources specifications sequential number_of_workers stdin json_pretty json_lines output_diff verbose match_timeout in_place dump_statistics file_extensions
run matcher configuration
]
let default_command =

View File

@ -47,41 +47,11 @@ type json_match_result =
type json_rewrite_result =
{ rewritten_source : string
; in_place_substitutions : Rewrite.match_context_replacement list
; in_place_substitutions : Replacement.t list
; id : int
}
[@@deriving yojson]
let matcher_of_file_extension extension =
let (module M : Matchers.Matcher) =
match extension with
| ".c" | ".h" | ".cc" | ".cpp" | ".hpp" -> (module Matchers.C)
| ".clj" -> (module Matchers.Clojure)
| ".css" -> (module Matchers.CSS)
| ".dart" -> (module Matchers.Dart)
| ".elm" -> (module Matchers.Elm)
| ".erl" -> (module Matchers.Erlang)
| ".ex" -> (module Matchers.Elixir)
| ".html" | ".xml" -> (module Matchers.Html)
| ".hs" -> (module Matchers.Haskell)
| ".go" -> (module Matchers.Go)
| ".java" -> (module Matchers.Java)
| ".js" | ".ts" -> (module Matchers.Javascript)
| ".ml" | ".mli" -> (module Matchers.OCaml)
| ".php" -> (module Matchers.Php)
| ".py" -> (module Matchers.Python)
| ".rb" -> (module Matchers.Ruby)
| ".rs" -> (module Matchers.Rust)
| ".s" | ".asm" -> (module Matchers.Assembly)
| ".scala" -> (module Matchers.Scala)
| ".sql" -> (module Matchers.SQL)
| ".sh" -> (module Matchers.Bash)
| ".swift" -> (module Matchers.Swift)
| ".tex" | ".bib" -> (module Matchers.Latex)
| _ -> (module Matchers.Generic)
in
(module M : Matchers.Matcher)
let get_matches (module Matcher : Matchers.Matcher) source match_template =
let configuration = Configuration.create ~match_kind:Fuzzy () in
Matcher.all ~configuration ~template:match_template ~source
@ -120,7 +90,7 @@ let perform_match request =
>>| function
| Ok ({ source; match_template; rule; language; id } as request) ->
if debug then Format.printf "Received %s@." (Yojson.Safe.pretty_to_string (match_request_to_yojson request));
let matcher = matcher_of_file_extension language in
let matcher = Matchers.select_with_extension language in
let run ?rule () =
get_matches matcher source match_template
|> Option.value_map rule ~default:ident ~f:(apply_rule matcher)
@ -138,7 +108,7 @@ let perform_match request =
if debug then Format.printf "Result (400) %s@." error;
respond ~code:(`Code 400) (`String error)
let rewrite_to_json id ({ rewritten_source; in_place_substitutions } : Rewrite.result) =
let rewrite_to_json id ({ rewritten_source; in_place_substitutions } : Replacement.result) =
Format.sprintf "%s"
(Yojson.Safe.pretty_to_string
(json_rewrite_result_to_yojson
@ -159,7 +129,7 @@ let perform_rewrite request =
>>| function
| Ok ({ source; match_template; rewrite_template; rule; language; substitution_kind; id } as request) ->
if debug then Format.printf "Received %s@." (Yojson.Safe.pretty_to_string (rewrite_request_to_yojson request));
let matcher = matcher_of_file_extension language in
let matcher = Matchers.select_with_extension language in
let source_substitution =
match substitution_kind with
| "newline_separated" -> None

300
test/#test_cli.ml# Normal file
View File

@ -0,0 +1,300 @@
open Core
module Time = Core_kernel.Time_ns.Span
let binary_path = "../../../comby"
let read_with_timeout read_from_channels =
let read_from_fds = List.map ~f:Unix.descr_of_in_channel read_from_channels in
let read_from_channel =
Unix.select
~read:read_from_fds
~write:[]
~except:[]
~timeout:(`After (Time.of_int_sec 5))
()
|> (fun { Unix.Select_fds.read; _ } -> List.hd_exn read)
|> Unix.in_channel_of_descr
in
In_channel.input_all read_from_channel
let read_source_from_stdin command source =
let open Unix.Process_channels in
let { stdin; stdout; stderr } = Unix.open_process_full ~env:[||] command in
Out_channel.output_string stdin source;
Out_channel.flush stdin;
Out_channel.close stdin;
read_with_timeout [stdout; stderr]
let read_output command =
let open Unix.Process_channels in
let { stdout; stderr; _ } = Unix.open_process_full ~env:[||] command in
read_with_timeout [stdout; stderr]
let%expect_test "error_on_zip_and_stdin" =
let command_args = "-zip x -stdin" in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command "none"
|> print_string;
[%expect_exact {|No templates specified. Either on the command line, or using -templates <directory-containing-templates>
Next error: -zip may not be used with stdin.
|}]
let%expect_test "warn_on_anonymous_and_templates_flag" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .c -templates nonexistent" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|Warning: Templates specified on the command line AND using -templates. Ignoring match
and rewrite templates on the command line and only using those in directories.
(Failure "Could not read required match file nonexistent/match")
|}]
let%expect_test "warn_json_lines_and_json_pretty" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .c -json-lines -json-pretty" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|Warning: Both -json-lines and -json-pretty specified. Using -json-pretty.
|}]
let%expect_test "stdin_command" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .c" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|world|}]
let%expect_test "with_match_rule" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let rule = {|where :[1] == "world"|} in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -rule '%s' -f .c "
match_template rewrite_template rule
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|world|}];
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let rule = {|where :[1] != "world"|} in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -rule '%s' -f .c "
match_template rewrite_template rule
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|hello world|}]
let%expect_test "with_rewrite_rule" =
let source = "hello world" in
let match_template = ":[2] :[1]" in
let rewrite_template = ":[1]" in
let rule = {|where rewrite :[1] { | ":[_]" -> ":[2]" }|} in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -rule '%s' -f .c "
match_template rewrite_template rule
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|hello|}]
let%expect_test "with_rewrite_rule_stdin_default_no_extension" =
let source = "hello world" in
let match_template = ":[2] :[1]" in
let rewrite_template = ":[1]" in
let rule = {|where rewrite :[1] { | ":[_]" -> ":[2]" }|} in
let command_args =
Format.sprintf "-sequential '%s' '%s' -rule '%s'"
match_template rewrite_template rule
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|hello|}]
let%expect_test "generic_matcher" =
let source = {|\footnote{\small \url{https://github.com}}|} in
let match_template = {|\footnote{\small :[1]}|} in
let rewrite_template = {|\footnote{\scriptsize :[1]}|} in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .generic" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|\footnote{\scriptsize \url{https://github.com}}|}]
let%expect_test "json_output_option" =
let source = "a X c a Y c" in
let match_template = "a :[1] c" in
let rewrite_template = "c :[1] a" in
let command_args =
Format.sprintf "-stdin -sequential -json-pretty '%s' '%s' -f .c "
match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|{
"uri": null,
"rewritten_source": "c X a c Y a",
"in_place_substitutions": [
{
"range": {
"start": { "offset": 6, "line": -1, "column": -1 },
"end": { "offset": 11, "line": -1, "column": -1 }
},
"replacement_content": "c Y a",
"environment": [
{
"variable": "1",
"value": "Y",
"range": {
"start": { "offset": 2, "line": -1, "column": -1 },
"end": { "offset": 3, "line": -1, "column": -1 }
}
}
]
},
{
"range": {
"start": { "offset": 0, "line": -1, "column": -1 },
"end": { "offset": 5, "line": -1, "column": -1 }
},
"replacement_content": "c X a",
"environment": [
{
"variable": "1",
"value": "X",
"range": {
"start": { "offset": 2, "line": -1, "column": -1 },
"end": { "offset": 3, "line": -1, "column": -1 }
}
}
]
}
]
}|}];
let source = "a X c a Y c" in
let match_template = "a :[1] c" in
let rewrite_template = "c :[1] a" in
let command_args =
Format.sprintf "-stdin -sequential -json-pretty -match-only '%s' '%s' -f .c "
match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|{
"uri": null,
"matches": [
{
"range": {
"start": { "offset": 0, "line": 1, "column": 1 },
"end": { "offset": 5, "line": 1, "column": 6 }
},
"environment": [
{
"variable": "1",
"value": "X",
"range": {
"start": { "offset": 2, "line": 1, "column": 3 },
"end": { "offset": 3, "line": 1, "column": 4 }
}
}
],
"matched": "a X c"
},
{
"range": {
"start": { "offset": 6, "line": 1, "column": 7 },
"end": { "offset": 11, "line": 1, "column": 12 }
},
"environment": [
{
"variable": "1",
"value": "Y",
"range": {
"start": { "offset": 8, "line": 1, "column": 9 },
"end": { "offset": 9, "line": 1, "column": 10 }
}
}
],
"matched": "a Y c"
}
]
}|}]
let with_zip f =
let file = Filename.temp_file "comby_" ".zip" in
let zip = Zip.open_out file in
let entry_name = "main.ml" in
let entry_content = "hello world" in
Zip.add_entry entry_content zip entry_name;
Zip.close_out zip;
f file;
Unix.remove file
let%expect_test "patdiff_and_zip" =
with_zip (fun file ->
let match_template = ":[2] :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "'%s' '%s' .ml -sequential -json-pretty -zip %s"
match_template rewrite_template file
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_output command
|> print_string;
[%expect_exact {|{
"uri": "main.ml",
"rewritten_source": "world",
"in_place_substitutions": [
{
"range": {
"start": { "offset": 0, "line": -1, "column": -1 },
"end": { "offset": 5, "line": -1, "column": -1 }
},
"replacement_content": "world",
"environment": [
{
"variable": "1",
"value": "world",
"range": {
"start": { "offset": 0, "line": -1, "column": -1 },
"end": { "offset": 5, "line": -1, "column": -1 }
}
}
]
}
],
"diff": "--- main.ml\n+++ main.ml\n@@ -1,1 +1,1 @@\n -hello world\n +world"
}|}]
)

View File

@ -4,11 +4,11 @@ module Time = Core_kernel.Time_ns.Span
let binary_path = "../../../comby"
let read_with_timeout read_from_channel =
let read_from_fd = Unix.descr_of_in_channel read_from_channel in
let read_with_timeout read_from_channels =
let read_from_fds = List.map ~f:Unix.descr_of_in_channel read_from_channels in
let read_from_channel =
Unix.select
~read:[read_from_fd]
~read:read_from_fds
~write:[]
~except:[]
~timeout:(`After (Time.of_int_sec 5))
@ -20,16 +20,55 @@ let read_with_timeout read_from_channel =
let read_source_from_stdin command source =
let open Unix.Process_channels in
let { stdin; stdout; stderr = _ } = Unix.open_process_full ~env:[||] command in
let { stdin; stdout; stderr } = Unix.open_process_full ~env:[||] command in
Out_channel.output_string stdin source;
Out_channel.flush stdin;
Out_channel.close stdin;
read_with_timeout stdout
read_with_timeout [stdout; stderr]
let read_output command =
let open Unix.Process_channels in
let { stdout; _ } = Unix.open_process_full ~env:[||] command in
read_with_timeout stdout
let { stdout; stderr; _ } = Unix.open_process_full ~env:[||] command in
read_with_timeout [stdout; stderr]
let%expect_test "error_on_zip_and_stdin" =
let command_args = "-zip x -stdin" in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command "none"
|> print_string;
[%expect_exact {|No templates specified. Either on the command line, or using -templates <directory-containing-templates>
Next error: -zip may not be used with stdin.
|}]
let%expect_test "warn_on_anonymous_and_templates_flag" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .c -templates nonexistent" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|Warning: Templates specified on the command line AND using -templates. Ignoring match
and rewrite templates on the command line and only using those in directories.
(Failure "Could not read required match file nonexistent/match")
|}]
let%expect_test "warn_json_lines_and_json_pretty" =
let source = "hello world" in
let match_template = "hello :[1]" in
let rewrite_template = ":[1]" in
let command_args =
Format.sprintf "-stdin -sequential '%s' '%s' -f .c -json-lines -json-pretty" match_template rewrite_template
in
let command = Format.sprintf "%s %s" binary_path command_args in
read_source_from_stdin command source
|> print_string;
[%expect_exact {|Warning: Both -json-lines and -json-pretty specified. Using -json-pretty.
|}]
let%expect_test "stdin_command" =
let source = "hello world" in
@ -160,7 +199,9 @@ let%expect_test "json_output_option" =
}
]
}
]
],
"diff":
"--- /dev/null\n+++ /dev/null\n@@ -1,1 +1,1 @@\n -a X c a Y c\n +c X a c Y a"
}|}];
let source = "a X c a Y c" in

View File

@ -51,7 +51,7 @@ let%expect_test "comments_in_string_literals_should_not_be_treated_as_comments_b
all match_template source
|> Rewrite.all ~source ~rewrite_template
|> (function
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Rewrite.result_to_yojson rewrite_result))
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Replacement.result_to_yojson rewrite_result))
| None -> print_string "BROKEN EXPECT");
[%expect_exact {|{
"rewritten_source": "123433312343331122",
@ -99,7 +99,7 @@ let%expect_test "comments_in_string_literals_should_not_be_treated_as_comments_b
all match_template source
|> Rewrite.all ~source ~rewrite_template
|> (function
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Rewrite.result_to_yojson rewrite_result))
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Replacement.result_to_yojson rewrite_result))
| None -> print_string "BROKEN EXPECT");
[%expect_exact {|{
"rewritten_source": "123433312343331122;123433312343331122;",
@ -180,7 +180,7 @@ let%expect_test "multiple_contextual_substitutions" =
all match_template source
|> Rewrite.all ~source ~rewrite_template
|> (function
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Rewrite.result_to_yojson rewrite_result))
| Some rewrite_result -> print_string (Yojson.Safe.pretty_to_string (Replacement.result_to_yojson rewrite_result))
| None -> print_string "BROKEN EXPECT");
[%expect_exact {|{
"rewritten_source": "xxxx bar xxxx",