Skip to content

Commit

Permalink
unstable-fmt: ignore files in OCaml syntax (#1784)
Browse files Browse the repository at this point in the history
* unstable-fmt: ignore files in OCaml syntax

When this is detected, it displays a warning and does nothing.

Signed-off-by: Etienne Millon <me@emillon.org>
  • Loading branch information
emillon authored Jan 28, 2019
1 parent ca9d3b3 commit 15bb1b6
Show file tree
Hide file tree
Showing 6 changed files with 38 additions and 24 deletions.
2 changes: 2 additions & 0 deletions CHANGES.md
Original file line number Diff line number Diff line change
Expand Up @@ -110,6 +110,8 @@ unreleased
stanza. It was previously causing intermediate *mock* files to be
promoted (#1783, fixes #1781, @diml)

- unstable-fmt: ignore files using OCaml syntax (#1784, @emillon)

1.6.2 (05/12/2018)
------------------

Expand Down
32 changes: 18 additions & 14 deletions src/dune_fmt.ml
Original file line number Diff line number Diff line change
@@ -1,20 +1,22 @@
open! Stdune
open! Import

type dune_file =
| OCaml_syntax of Loc.t
| Sexps of Dune_lang.Cst.t list

let parse_lexbuf lb =
if Dune_lexer.is_script lb then
OCaml_syntax (Loc.of_lexbuf lb)
else
Sexps (Dune_lang.Parser.parse_cst lb)

let parse_file path_opt =
let fname, contents =
match path_opt with
| Some path ->
Io.with_file_in path ~f:(fun ic ->
let contents = Io.read_all ic in
(Path.to_string path, contents)
)
| None ->
let lines = Io.input_lines stdin in
let contents = String.concat ~sep:"\n" lines in
("<stdin>", contents)
in
Dune_lang.parse_cst_string ~fname contents
match path_opt with
| Some path ->
Io.with_lexbuf_from_file path ~f:parse_lexbuf
| None ->
parse_lexbuf @@ Lexing.from_channel stdin

let can_be_displayed_wrapped =
List.for_all ~f:(fun (c : Dune_lang.Cst.t) ->
Expand Down Expand Up @@ -131,7 +133,9 @@ let format_file ~input ~output =
Printf.printf
"Parse error: %s\n"
(Dune_lang.Parse_error.message e)
| sexps ->
| OCaml_syntax loc ->
Errors.warn loc "OCaml syntax is not supported, skipping."
| Sexps sexps ->
with_output output (fun fmt ->
pp_top_sexps fmt sexps;
Format.pp_print_flush fmt ()
Expand Down
4 changes: 0 additions & 4 deletions src/dune_lang/dune_lang.ml
Original file line number Diff line number Diff line change
Expand Up @@ -361,10 +361,6 @@ let parse_string ~fname ~mode ?lexer str =
let lb = lexbuf_from_string ~fname str in
Parser.parse ~mode ?lexer lb

let parse_cst_string ~fname ?lexer str =
let lb = lexbuf_from_string ~fname str in
Parser.parse_cst ?lexer lb

type dune_lang = t

module Encoder = struct
Expand Down
6 changes: 0 additions & 6 deletions src/dune_lang/dune_lang.mli
Original file line number Diff line number Diff line change
Expand Up @@ -206,12 +206,6 @@ val parse_string
-> string
-> 'a

val parse_cst_string
: fname:string
-> ?lexer:Lexer.t
-> string
-> Cst.t list

module Encoder : sig
type sexp = t
include Sexp_intf.Combinators with type 'a t = 'a -> t
Expand Down
7 changes: 7 additions & 0 deletions test/blackbox-tests/test-cases/fmt/ocaml-syntax.dune
Original file line number Diff line number Diff line change
@@ -0,0 +1,7 @@
(* -*- tuareg -*- *)

let () = Jbuild_plugin.V1.send {|
(alias
(name runtest)
(action (echo "ocaml syntax")))
|}
11 changes: 11 additions & 0 deletions test/blackbox-tests/test-cases/fmt/run.t
Original file line number Diff line number Diff line change
Expand Up @@ -164,3 +164,14 @@ When a comment is at the end of a list, the ")" is on a own line.
; final unattached
; multiline
)
Files in OCaml syntax are ignored with a warning.
$ dune unstable-fmt < ocaml-syntax.dune
File "", line 1, characters 0-20:
Warning: OCaml syntax is not supported, skipping.
$ dune unstable-fmt ocaml-syntax.dune
File "$TESTCASE_ROOT/ocaml-syntax.dune", line 1, characters 0-20:
1 | (* -*- tuareg -*- *)
^^^^^^^^^^^^^^^^^^^^
Warning: OCaml syntax is not supported, skipping.

0 comments on commit 15bb1b6

Please sign in to comment.